module Graphics.UI.Qtah.Generator.Interface.Core.QChar (
aModule,
c_QChar,
) where
import Control.Monad (guard)
import Foreign.Hoppy.Generator.Language.Haskell (
addImports,
sayLn,
)
import Foreign.Hoppy.Generator.Spec (
ClassHaskellConversion (
ClassHaskellConversion,
classHaskellConversionFromCppFn,
classHaskellConversionToCppFn,
classHaskellConversionType
),
addReqIncludes,
classSetEntityPrefix,
classSetHaskellConversion,
hsImport1,
ident,
ident1,
includeStd,
makeClass,
mkConstMethod,
mkConstMethod',
mkCtor,
mkMethod',
mkStaticMethod,
mkStaticMethod',
np,
)
import Foreign.Hoppy.Generator.Spec.ClassFeature (
ClassFeature (Assignable, Copyable, Comparable, Equatable),
classAddFeatures,
)
import Foreign.Hoppy.Generator.Types (
boolT,
charT,
intT,
enumT,
objT,
refT,
char16T,
ucharT,
ushortT,
uintT,
)
import Foreign.Hoppy.Generator.Version (collect, just, test)
import Graphics.UI.Qtah.Generator.Config (qtVersion)
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Core.QString (c_QString)
import Graphics.UI.Qtah.Generator.Interface.Imports
import Graphics.UI.Qtah.Generator.Module (AModule (AQtModule), makeQtModule)
import Graphics.UI.Qtah.Generator.Types
import Language.Haskell.Syntax (
HsName (HsIdent),
HsQName (UnQual),
HsType (HsTyCon),
)
{-# ANN module "HLint: ignore Use camelCase" #-}
aModule :: AModule
aModule =
QtModule -> AModule
AQtModule (QtModule -> AModule) -> QtModule -> AModule
forall a b. (a -> b) -> a -> b
$
[String] -> [QtExport] -> QtModule
makeQtModule [String
"Core", String
"QChar"] ([QtExport] -> QtModule) -> [QtExport] -> QtModule
forall a b. (a -> b) -> a -> b
$
[Filtered QtExport] -> [QtExport]
forall a. [Filtered a] -> [a]
collect
[ QtExport -> Filtered QtExport
forall a. a -> Filtered a
just (QtExport -> Filtered QtExport) -> QtExport -> Filtered QtExport
forall a b. (a -> b) -> a -> b
$ Class -> QtExport
forall a. Exportable a => a -> QtExport
qtExport Class
c_QChar
, QtExport -> Filtered QtExport
forall a. a -> Filtered a
just (QtExport -> Filtered QtExport) -> QtExport -> Filtered QtExport
forall a b. (a -> b) -> a -> b
$ CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_Category
, QtExport -> Filtered QtExport
forall a. a -> Filtered a
just (QtExport -> Filtered QtExport) -> QtExport -> Filtered QtExport
forall a b. (a -> b) -> a -> b
$ CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_Decomposition
, Bool -> QtExport -> Filtered QtExport
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
< [Int
5, Int
3]) (QtExport -> Filtered QtExport) -> QtExport -> Filtered QtExport
forall a b. (a -> b) -> a -> b
$ CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_Joining
, Bool -> QtExport -> Filtered QtExport
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
3]) (QtExport -> Filtered QtExport) -> QtExport -> Filtered QtExport
forall a b. (a -> b) -> a -> b
$ CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_JoiningType
, Bool -> QtExport -> Filtered QtExport
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
1]) (QtExport -> Filtered QtExport) -> QtExport -> Filtered QtExport
forall a b. (a -> b) -> a -> b
$ CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_Script
, QtExport -> Filtered QtExport
forall a. a -> Filtered a
just (QtExport -> Filtered QtExport) -> QtExport -> Filtered QtExport
forall a b. (a -> b) -> a -> b
$ CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_Direction
, QtExport -> Filtered QtExport
forall a. a -> Filtered a
just (QtExport -> Filtered QtExport) -> QtExport -> Filtered QtExport
forall a b. (a -> b) -> a -> b
$ CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_SpecialCharacter
, QtExport -> Filtered QtExport
forall a. a -> Filtered a
just (QtExport -> Filtered QtExport) -> QtExport -> Filtered QtExport
forall a b. (a -> b) -> a -> b
$ CppEnum -> QtExport
forall a. Exportable a => a -> QtExport
qtExport CppEnum
e_UnicodeVersion
]
c_QChar :: Class
c_QChar =
[Include] -> Class -> Class
forall a. HasReqs a => [Include] -> a -> a
addReqIncludes [String -> Include
includeStd String
"QChar"] (Class -> Class) -> Class -> Class
forall a b. (a -> b) -> a -> b
$
[ClassFeature] -> Class -> Class
classAddFeatures [ClassFeature
Assignable, ClassFeature
Copyable, ClassFeature
Comparable, ClassFeature
Equatable] (Class -> Class) -> Class -> Class
forall a b. (a -> b) -> a -> b
$
ClassHaskellConversion -> Class -> Class
classSetHaskellConversion
ClassHaskellConversion
{ classHaskellConversionType :: Maybe (Generator HsType)
classHaskellConversionType = Generator HsType -> Maybe (Generator HsType)
forall a. a -> Filtered a
Just (Generator HsType -> Maybe (Generator HsType))
-> Generator HsType -> Maybe (Generator HsType)
forall a b. (a -> b) -> a -> b
$ do
HsImportSet -> Generator ()
addImports HsImportSet
importForPrelude
HsType -> Generator HsType
forall a. a -> ReaderT Env (WriterT Output (Except String)) a
forall (m :: * -> *) a. Monad m => a -> m a
return (HsType -> Generator HsType) -> HsType -> Generator HsType
forall a b. (a -> b) -> a -> b
$ HsQName -> HsType
HsTyCon (HsQName -> HsType) -> HsQName -> HsType
forall a b. (a -> b) -> a -> b
$ HsName -> HsQName
UnQual (HsName -> HsQName) -> HsName -> HsQName
forall a b. (a -> b) -> a -> b
$ String -> HsName
HsIdent String
"QtahP.Char"
, classHaskellConversionToCppFn :: Maybe (Generator ())
classHaskellConversionToCppFn = Generator () -> Maybe (Generator ())
forall a. a -> Filtered a
Just (Generator () -> Maybe (Generator ()))
-> Generator () -> Maybe (Generator ())
forall a b. (a -> b) -> a -> b
$ do
HsImportSet -> Generator ()
addImports (HsImportSet -> Generator ()) -> HsImportSet -> Generator ()
forall a b. (a -> b) -> a -> b
$ [HsImportSet] -> HsImportSet
forall a. Monoid a => [a] -> a
mconcat [String -> String -> HsImportSet
hsImport1 String
"Prelude" String
"(.)", HsImportSet
importForChar, HsImportSet
importForRuntime]
String -> Generator ()
sayLn String
"newFromInt . QtahFHR.coerceIntegral . QtahDC.ord"
, classHaskellConversionFromCppFn :: Maybe (Generator ())
classHaskellConversionFromCppFn = Generator () -> Maybe (Generator ())
forall a. a -> Filtered a
Just (Generator () -> Maybe (Generator ()))
-> Generator () -> Maybe (Generator ())
forall a b. (a -> b) -> a -> b
$ do
HsImportSet -> Generator ()
addImports (HsImportSet -> Generator ()) -> HsImportSet -> Generator ()
forall a b. (a -> b) -> a -> b
$ [HsImportSet] -> HsImportSet
forall a. Monoid a => [a] -> a
mconcat [String -> String -> HsImportSet
hsImport1 String
"Prelude" String
"(.)", HsImportSet
importForChar, HsImportSet
importForPrelude,
HsImportSet
importForRuntime]
String -> Generator ()
sayLn String
"QtahP.fmap (QtahDC.chr . QtahFHR.coerceIntegral) . unicode"
} (Class -> Class) -> Class -> Class
forall a b. (a -> b) -> a -> b
$
String -> Class -> Class
classSetEntityPrefix String
"" (Class -> Class) -> Class -> Class
forall a b. (a -> b) -> a -> b
$
Identifier -> Maybe ExtName -> [Class] -> [ClassEntity] -> Class
makeClass (String -> Identifier
ident String
"QChar") Maybe ExtName
forall a. Maybe a
Nothing [] ([ClassEntity] -> Class) -> [ClassEntity] -> Class
forall a b. (a -> b) -> a -> b
$
[Filtered ClassEntity] -> [ClassEntity]
forall a. [Filtered a] -> [a]
collect
[ ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> ClassEntity
forall p. IsParameter p => String -> [p] -> ClassEntity
mkCtor String
"new" [Parameter]
np
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> ClassEntity
forall p. IsParameter p => String -> [p] -> ClassEntity
mkCtor String
"newFromCellRow" [Type
ucharT, Type
ucharT]
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> ClassEntity
forall p. IsParameter p => String -> [p] -> ClassEntity
mkCtor String
"newFromInt" [Type
intT]
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> ClassEntity
forall p. IsParameter p => String -> [p] -> ClassEntity
mkCtor String
"newFromSpecialCharacter" [CppEnum -> Type
enumT CppEnum
e_SpecialCharacter]
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
< [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"fromAscii" String
"newFromAscii" [Type
charT] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QChar
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"category" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_Category
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"cell" [Parameter]
np Type
ucharT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"combiningClass" [Parameter]
np Type
ucharT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"decomposition" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QString
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"decompositionTag" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_Decomposition
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"digitValue" [Parameter]
np Type
intT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"direction" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_Direction
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"hasMirrored" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isDigit" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isHighSurrogate" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isLetter" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isLetterOrNumber" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isLowSurrogate" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isLower" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isMark" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isNull" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isNumber" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isPrint" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isPunct" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isSpace" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isSymbol" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isTitleCase" [Parameter]
np Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"isUpper" [Parameter]
np Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
< [Int
5, Int
3]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"joining" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_Joining
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
3]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"joiningType" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_JoiningType
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"mirroredChar" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QChar
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"row" [Parameter]
np Type
ucharT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
1]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"script" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_Script
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
< [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"toAscii" [Parameter]
np Type
charT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"toCaseFolded" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QChar
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"toLatin1" [Parameter]
np Type
charT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"toLower" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QChar
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"toTitleCase" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QChar
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"toUpper" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QChar
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkConstMethod' String
"unicode" String
"unicode" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$
if Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
6] then Type
char16T else Type
ushortT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkMethod' String
"unicode" String
"unicodeRef" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$
Type -> Type
refT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ if Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
6] then Type
char16T else Type
ushortT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkConstMethod String
"unicodeVersion" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_UnicodeVersion
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkStaticMethod String
"fromLatin1" [Type
charT] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QChar
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Parameter] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkStaticMethod String
"currentUnicodeVersion" [Parameter]
np (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_UnicodeVersion
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"category" String
"categoryStatic" [Type
uintT] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_Category
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"combiningClass" String
"combiningClassStatic" [Type
uintT] Type
ucharT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"decomposition" String
"decompositionStatic" [Type
uintT] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QString
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"decompositionTag" String
"decompositionTagStatic" [Type
uintT] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_Decomposition
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"digitValue" String
"digitValueStatic" [Type
uintT] Type
intT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"direction" String
"directionStatic" [Type
uintT] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_Direction
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"hasMirrored" String
"hasMirroredStatic" [Type
uintT] Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkStaticMethod String
"highSurrogate" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isDigit" String
"isDigitStatic" [Type
uintT] Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isHighSurrogate" String
"isHighSurrogateStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isLetter" String
"isLetterStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isLetterOrNumber" String
"isLetterOrNumberStatic" [Type
uintT] Type
boolT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isLowSurrogate" String
"isLowSurrogateStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isLower" String
"isLowerStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isMark" String
"isMarkStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isNonCharacter" String
"isNonCharacterStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isNumber" String
"isNumberStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isPrint" String
"isPrintStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isPunct" String
"isPunctStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isSpace" String
"isSpaceStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isSurrogate" String
"isSurrogateStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isSymbol" String
"isSymbolStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isTitleCase" String
"isTitleCaseStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"isUpper" String
"isUpperStatic" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
3]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"joiningType" String
"joiningTypeStatic" [Type
uintT] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_JoiningType
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkStaticMethod String
"lowSurrogate" [Type
uintT] Type
ushortT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"mirroredChar" String
"mirroredCharStatic" [Type
uintT] Type
uintT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> [p] -> Type -> ClassEntity
mkStaticMethod String
"requiresSurrogates" [Type
uintT] Type
boolT
, Bool -> ClassEntity -> Filtered ClassEntity
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
1]) (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"script" String
"scriptStatic" [Type
uintT] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_Script
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"surrogateToUcs4" String
"surrogateToUcs4" [Type
ushortT, Type
ushortT] Type
uintT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"surrogateToUcs4" String
"surrogateToUcs4WithQChar" [Class -> Type
objT Class
c_QChar, Class -> Type
objT Class
c_QChar] Type
uintT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"toCaseFolded" String
"toCaseFoldedStatic" [Type
uintT] Type
uintT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"toLower" String
"toLowerStatic" [Type
uintT] Type
uintT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"toTitleCase" String
"toTitleCaseStatic" [Type
uintT] Type
uintT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"toUpper" String
"toUpperStatic" [Type
uintT] Type
uintT
, ClassEntity -> Filtered ClassEntity
forall a. a -> Filtered a
just (ClassEntity -> Filtered ClassEntity)
-> ClassEntity -> Filtered ClassEntity
forall a b. (a -> b) -> a -> b
$ String -> String -> [Type] -> Type -> ClassEntity
forall name p.
(IsFnName String name, IsParameter p) =>
name -> String -> [p] -> Type -> ClassEntity
mkStaticMethod' String
"unicodeVersion" String
"unicodeVersionStatic" [Type
uintT] (Type -> ClassEntity) -> Type -> ClassEntity
forall a b. (a -> b) -> a -> b
$ CppEnum -> Type
enumT CppEnum
e_UnicodeVersion
]
e_Category :: CppEnum
e_Category =
Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QChar" String
"Category") [String -> Include
includeStd String
"QChar"] ([String] -> CppEnum) -> [String] -> CppEnum
forall a b. (a -> b) -> a -> b
$
[Filtered String] -> [String]
forall a. [Filtered a] -> [a]
collect
[
String -> Filtered String
forall a. a -> Filtered a
just String
"Mark_NonSpacing"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Mark_SpacingCombining"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Mark_Enclosing"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Number_DecimalDigit"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Number_Letter"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Number_Other"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Separator_Space"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Separator_Line"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Separator_Paragraph"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Other_Control"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Other_Format"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Other_Surrogate"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Other_PrivateUse"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Other_NotAssigned"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Letter_Uppercase"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Letter_Lowercase"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Letter_Titlecase"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Letter_Modifier"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Letter_Other"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Punctuation_Connector"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Punctuation_Dash"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Punctuation_Open"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Punctuation_Close"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Punctuation_InitialQuote"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Punctuation_FinalQuote"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Punctuation_Other"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Symbol_Math"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Symbol_Currency"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Symbol_Modifier"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Symbol_Other"
, Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
<= [Int
5, Int
0]) String
"NoCategory"
]
e_Decomposition :: CppEnum
e_Decomposition =
Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QChar" String
"Decomposition") [String -> Include
includeStd String
"QChar"]
[ String
"NoDecomposition"
, String
"Canonical"
, String
"Circle"
, String
"Compat"
, String
"Final"
, String
"Font"
, String
"Fraction"
, String
"Initial"
, String
"Isolated"
, String
"Medial"
, String
"Narrow"
, String
"NoBreak"
, String
"Small"
, String
"Square"
, String
"Sub"
, String
"Super"
, String
"Vertical"
, String
"Wide"
]
e_Direction :: CppEnum
e_Direction =
Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QChar" String
"Direction") [String -> Include
includeStd String
"QChar"]
[ String
"DirAL"
, String
"DirAN"
, String
"DirB"
, String
"DirBN"
, String
"DirCS"
, String
"DirEN"
, String
"DirES"
, String
"DirET"
, String
"DirL"
, String
"DirLRE"
, String
"DirLRO"
, String
"DirNSM"
, String
"DirON"
, String
"DirPDF"
, String
"DirR"
, String
"DirRLE"
, String
"DirRLO"
, String
"DirS"
, String
"DirWS"
]
e_Joining :: CppEnum
e_Joining =
Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QChar" String
"Joining") [String -> Include
includeStd String
"QChar"]
[ String
"Center"
, String
"Dual"
, String
"OtherJoining"
, String
"Right"
]
e_JoiningType :: CppEnum
e_JoiningType =
Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QChar" String
"JoiningType") [String -> Include
includeStd String
"QChar"]
[ String
"Joining_None"
, String
"Joining_Causing"
, String
"Joining_Dual"
, String
"Joining_Right"
, String
"Joining_Left"
, String
"Joining_Transparent"
]
e_SpecialCharacter :: CppEnum
e_SpecialCharacter =
Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QChar" String
"SpecialCharacter") [String -> Include
includeStd String
"QChar"] ([String] -> CppEnum) -> [String] -> CppEnum
forall a b. (a -> b) -> a -> b
$
[Filtered String] -> [String]
forall a. [Filtered a] -> [a]
collect
[ String -> Filtered String
forall a. a -> Filtered a
just String
"Null"
, Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
0]) String
"Tabulation"
, Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
0]) String
"LineFeed"
, Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
0]) String
"CarriageReturn"
, Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
0]) String
"Space"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Nbsp"
, Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
0]) String
"SoftHyphen"
, String -> Filtered String
forall a. a -> Filtered a
just String
"ReplacementCharacter"
, String -> Filtered String
forall a. a -> Filtered a
just String
"ObjectReplacementCharacter"
, String -> Filtered String
forall a. a -> Filtered a
just String
"ByteOrderMark"
, String -> Filtered String
forall a. a -> Filtered a
just String
"ByteOrderSwapped"
, String -> Filtered String
forall a. a -> Filtered a
just String
"ParagraphSeparator"
, String -> Filtered String
forall a. a -> Filtered a
just String
"LineSeparator"
, Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
0]) String
"LastValidCodePoint"
]
e_UnicodeVersion :: CppEnum
e_UnicodeVersion =
Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QChar" String
"UnicodeVersion") [String -> Include
includeStd String
"QChar"] ([String] -> CppEnum) -> [String] -> CppEnum
forall a b. (a -> b) -> a -> b
$
[Filtered String] -> [String]
forall a. [Filtered a] -> [a]
collect
[ String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_1_1"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_2_0"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_2_1_2"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_3_0"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_3_1"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_3_2"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_4_0"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_4_1"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_5_0"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_5_1"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_5_2"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_6_0"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_6_1"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_6_2"
, Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
3]) String
"Unicode_6_3"
, Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
5]) String
"Unicode_7_0"
, Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
6]) String
"Unicode_8_0"
, Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
11]) String
"Unicode_9_0"
, Bool -> String -> Filtered String
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
11]) String
"Unicode_10_0"
, String -> Filtered String
forall a. a -> Filtered a
just String
"Unicode_Unassigned"
]
e_Script :: CppEnum
e_Script =
Identifier -> [Include] -> [String] -> CppEnum
makeQtEnum (String -> String -> Identifier
ident1 String
"QChar" String
"Script") [String -> Include
includeStd String
"QChar"] ([String] -> CppEnum) -> [String] -> CppEnum
forall a b. (a -> b) -> a -> b
$
[ String
"Script_Unknown"
, String
"Script_Inherited"
, String
"Script_Common"
, String
"Script_Latin"
, String
"Script_Greek"
, String
"Script_Cyrillic"
, String
"Script_Armenian"
, String
"Script_Hebrew"
, String
"Script_Arabic"
, String
"Script_Syriac"
, String
"Script_Thaana"
, String
"Script_Devanagari"
, String
"Script_Bengali"
, String
"Script_Gurmukhi"
, String
"Script_Gujarati"
, String
"Script_Oriya"
, String
"Script_Tamil"
, String
"Script_Telugu"
, String
"Script_Kannada"
, String
"Script_Malayalam"
, String
"Script_Sinhala"
, String
"Script_Thai"
, String
"Script_Lao"
, String
"Script_Tibetan"
, String
"Script_Myanmar"
, String
"Script_Georgian"
, String
"Script_Hangul"
, String
"Script_Ethiopic"
, String
"Script_Cherokee"
, String
"Script_CanadianAboriginal"
, String
"Script_Ogham"
, String
"Script_Runic"
, String
"Script_Khmer"
, String
"Script_Mongolian"
, String
"Script_Hiragana"
, String
"Script_Katakana"
, String
"Script_Bopomofo"
, String
"Script_Han"
, String
"Script_Yi"
, String
"Script_OldItalic"
, String
"Script_Gothic"
, String
"Script_Deseret"
, String
"Script_Tagalog"
, String
"Script_Hanunoo"
, String
"Script_Buhid"
, String
"Script_Tagbanwa"
, String
"Script_Coptic"
, String
"Script_Limbu"
, String
"Script_TaiLe"
, String
"Script_LinearB"
, String
"Script_Ugaritic"
, String
"Script_Shavian"
, String
"Script_Osmanya"
, String
"Script_Cypriot"
, String
"Script_Braille"
, String
"Script_Buginese"
, String
"Script_NewTaiLue"
, String
"Script_Glagolitic"
, String
"Script_Tifinagh"
, String
"Script_SylotiNagri"
, String
"Script_OldPersian"
, String
"Script_Kharoshthi"
, String
"Script_Balinese"
, String
"Script_Cuneiform"
, String
"Script_Phoenician"
, String
"Script_PhagsPa"
, String
"Script_Nko"
, String
"Script_Sundanese"
, String
"Script_Lepcha"
, String
"Script_OlChiki"
, String
"Script_Vai"
, String
"Script_Saurashtra"
, String
"Script_KayahLi"
, String
"Script_Rejang"
, String
"Script_Lycian"
, String
"Script_Carian"
, String
"Script_Lydian"
, String
"Script_Cham"
, String
"Script_TaiTham"
, String
"Script_TaiViet"
, String
"Script_Avestan"
, String
"Script_EgyptianHieroglyphs"
, String
"Script_Samaritan"
, String
"Script_Lisu"
, String
"Script_Bamum"
, String
"Script_Javanese"
, String
"Script_MeeteiMayek"
, String
"Script_ImperialAramaic"
, String
"Script_OldSouthArabian"
, String
"Script_InscriptionalParthian"
, String
"Script_InscriptionalPahlavi"
, String
"Script_OldTurkic"
, String
"Script_Kaithi"
, String
"Script_Batak"
, String
"Script_Brahmi"
, String
"Script_Mandaic"
, String
"Script_Chakma"
, String
"Script_MeroiticCursive"
, String
"Script_MeroiticHieroglyphs"
, String
"Script_Miao"
, String
"Script_Sharada"
, String
"Script_SoraSompeng"
, String
"Script_Takri"
, String
"Script_CaucasianAlbanian"
, String
"Script_BassaVah"
, String
"Script_Duployan"
, String
"Script_Elbasan"
, String
"Script_Grantha"
, String
"Script_PahawhHmong"
, String
"Script_Khojki"
, String
"Script_LinearA"
, String
"Script_Mahajani"
, String
"Script_Manichaean"
, String
"Script_MendeKikakui"
, String
"Script_Modi"
, String
"Script_Mro"
, String
"Script_OldNorthArabian"
, String
"Script_Nabataean"
, String
"Script_Palmyrene"
, String
"Script_PauCinHau"
, String
"Script_OldPermic"
, String
"Script_PsalterPahlavi"
, String
"Script_Siddham"
, String
"Script_Khudawadi"
, String
"Script_Tirhuta"
, String
"Script_WarangCiti"
] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
(Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
6]) [()] -> [String] -> [String]
forall a b. [a] -> [b] -> [b]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
[ String
"Script_Ahom"
, String
"Script_AnatolianHieroglyphs"
, String
"Script_Hatran"
, String
"Script_Multani"
, String
"Script_OldHungarian"
, String
"Script_SignWriting"
]) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
(Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= [Int
5, Int
11]) [()] -> [String] -> [String]
forall a b. [a] -> [b] -> [b]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
[ String
"Script_Adlam"
, String
"Script_Bhaiksuki"
, String
"Script_Marchen"
, String
"Script_Newa"
, String
"Script_Osage"
, String
"Script_Tangut"
, String
"Script_MasaramGondi"
, String
"Script_Nushu"
, String
"Script_Soyombo"
, String
"Script_ZanabazarSquare"
])