Copyright | (c) 2011-2018 Ian-Woo Kim |
---|---|
License | BSD3 |
Maintainer | Ian-Woo Kim <ianwookim@gmail.com> |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell98 |
Synopsis
- data CTypes
- = CTBool
- | CTChar
- | CTClock
- | CTDouble
- | CTFile
- | CTFloat
- | CTFpos
- | CTInt
- | CTIntMax
- | CTIntPtr
- | CTJmpBuf
- | CTLLong
- | CTLong
- | CTPtrdiff
- | CTSChar
- | CTSUSeconds
- | CTShort
- | CTSigAtomic
- | CTSize
- | CTTime
- | CTUChar
- | CTUInt
- | CTUIntMax
- | CTUIntPtr
- | CTULLong
- | CTULong
- | CTUSeconds
- | CTUShort
- | CTWchar
- | CTInt8
- | CTInt16
- | CTInt32
- | CTInt64
- | CTUInt8
- | CTUInt16
- | CTUInt32
- | CTUInt64
- | CTVoidStar
- | CTString
- | CEnum CTypes String
- | CPointer CTypes
- | CRef CTypes
- data CPPTypes
- data IsConst
- data TemplateArgType
- data TemplateAppInfo = TemplateAppInfo {}
- data Types
- type Args = [(Types, String)]
- data Function
- = Constructor {
- func_args :: Args
- func_alias :: Maybe String
- | Virtual { }
- | NonVirtual { }
- | Static { }
- | Destructor { }
- = Constructor {
- data Variable = Variable {}
- data TemplateMemberFunction = TemplateMemberFunction {}
- data TopLevelFunction
- isNewFunc :: Function -> Bool
- isDeleteFunc :: Function -> Bool
- isVirtualFunc :: Function -> Bool
- isNonVirtualFunc :: Function -> Bool
- isStaticFunc :: Function -> Bool
- virtualFuncs :: [Function] -> [Function]
- constructorFuncs :: [Function] -> [Function]
- nonVirtualNotNewFuncs :: [Function] -> [Function]
- staticFuncs :: [Function] -> [Function]
- newtype ProtectedMethod = Protected {
- unProtected :: [String]
- data ClassAlias = ClassAlias {}
- data Class
- = Class { }
- | AbstractClass { }
- data TemplateFunction
- = TFun { }
- | TFunNew { }
- | TFunDelete
- data TemplateClass = TmplCls {}
- data ClassGlobal = ClassGlobal {}
- data Selfness
- isAbstractClass :: Class -> Bool
- type DaughterMap = Map String [Class]
- data Accessor
Documentation
C types
C++ types
const flag
data TemplateArgType Source #
Argument type which can be used as an template argument like float in vectorfloat. For now, this distinguishes Class and non-Class.
Instances
Show TemplateArgType Source # | |
Defined in FFICXX.Generate.Type.Class showsPrec :: Int -> TemplateArgType -> ShowS # show :: TemplateArgType -> String # showList :: [TemplateArgType] -> ShowS # |
data TemplateAppInfo Source #
Instances
Show TemplateAppInfo Source # | |
Defined in FFICXX.Generate.Type.Class showsPrec :: Int -> TemplateAppInfo -> ShowS # show :: TemplateAppInfo -> String # showList :: [TemplateAppInfo] -> ShowS # |
Void | |
SelfType | |
CT CTypes IsConst | |
CPT CPPTypes IsConst | |
TemplateApp TemplateAppInfo | like vectorfloat* |
TemplateAppRef TemplateAppInfo | like vectorfloat& |
TemplateAppMove TemplateAppInfo | like unique_ptrfloat (using std::move) |
TemplateType TemplateClass | template self? TODO: clarify this. |
TemplateParam String | |
TemplateParamPointer String | this is A* with templateA |
data TemplateMemberFunction Source #
Instances
Show TemplateMemberFunction Source # | |
Defined in FFICXX.Generate.Type.Class showsPrec :: Int -> TemplateMemberFunction -> ShowS # show :: TemplateMemberFunction -> String # showList :: [TemplateMemberFunction] -> ShowS # |
data TopLevelFunction Source #
Instances
Show TopLevelFunction Source # | |
Defined in FFICXX.Generate.Type.Class showsPrec :: Int -> TopLevelFunction -> ShowS # show :: TopLevelFunction -> String # showList :: [TopLevelFunction] -> ShowS # |
isDeleteFunc :: Function -> Bool Source #
isVirtualFunc :: Function -> Bool Source #
isNonVirtualFunc :: Function -> Bool Source #
isStaticFunc :: Function -> Bool Source #
virtualFuncs :: [Function] -> [Function] Source #
constructorFuncs :: [Function] -> [Function] Source #
nonVirtualNotNewFuncs :: [Function] -> [Function] Source #
staticFuncs :: [Function] -> [Function] Source #
newtype ProtectedMethod Source #
Protected | |
|
Instances
Semigroup ProtectedMethod Source # | |
Defined in FFICXX.Generate.Type.Class (<>) :: ProtectedMethod -> ProtectedMethod -> ProtectedMethod # sconcat :: NonEmpty ProtectedMethod -> ProtectedMethod # stimes :: Integral b => b -> ProtectedMethod -> ProtectedMethod # | |
Monoid ProtectedMethod Source # | |
Defined in FFICXX.Generate.Type.Class mappend :: ProtectedMethod -> ProtectedMethod -> ProtectedMethod # mconcat :: [ProtectedMethod] -> ProtectedMethod # |
data ClassAlias Source #
Class | |
| |
AbstractClass | |
|
data TemplateClass Source #
TmplCls | |
|
Instances
Eq TemplateClass Source # | |
Defined in FFICXX.Generate.Type.Class (==) :: TemplateClass -> TemplateClass -> Bool # (/=) :: TemplateClass -> TemplateClass -> Bool # | |
Ord TemplateClass Source # | |
Defined in FFICXX.Generate.Type.Class compare :: TemplateClass -> TemplateClass -> Ordering # (<) :: TemplateClass -> TemplateClass -> Bool # (<=) :: TemplateClass -> TemplateClass -> Bool # (>) :: TemplateClass -> TemplateClass -> Bool # (>=) :: TemplateClass -> TemplateClass -> Bool # max :: TemplateClass -> TemplateClass -> TemplateClass # min :: TemplateClass -> TemplateClass -> TemplateClass # | |
Show TemplateClass Source # | |
Defined in FFICXX.Generate.Type.Class showsPrec :: Int -> TemplateClass -> ShowS # show :: TemplateClass -> String # showList :: [TemplateClass] -> ShowS # |
isAbstractClass :: Class -> Bool Source #
Check abstract class