Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data CFunSig = CFunSig {}
- data HsFunSig = HsFunSig {
- hsSigTypes :: [Type ()]
- hsSigConstraints :: [Asst ()]
- ctypToCType :: CTypes -> IsConst -> CType Identity
- self_ :: Types
- cstring_ :: Types
- cint_ :: Types
- int_ :: Types
- uint_ :: Types
- ulong_ :: Types
- long_ :: Types
- culong_ :: Types
- clong_ :: Types
- cchar_ :: Types
- char_ :: Types
- cshort_ :: Types
- short_ :: Types
- cdouble_ :: Types
- double_ :: Types
- doublep_ :: Types
- cfloat_ :: Types
- float_ :: Types
- bool_ :: Types
- void_ :: Types
- voidp_ :: Types
- intp_ :: Types
- intref_ :: Types
- charpp_ :: Types
- ref_ :: CTypes -> Types
- star_ :: CTypes -> Types
- cstar_ :: CTypes -> Types
- self :: String -> Arg
- voidp :: String -> Arg
- cstring :: String -> Arg
- cint :: String -> Arg
- int :: String -> Arg
- uint :: String -> Arg
- long :: String -> Arg
- ulong :: String -> Arg
- clong :: String -> Arg
- culong :: String -> Arg
- cchar :: String -> Arg
- char :: String -> Arg
- cshort :: String -> Arg
- short :: String -> Arg
- cdouble :: String -> Arg
- double :: String -> Arg
- doublep :: String -> Arg
- cfloat :: String -> Arg
- float :: String -> Arg
- bool :: String -> Arg
- intp :: String -> Arg
- intref :: String -> Arg
- charpp :: String -> Arg
- ref :: CTypes -> String -> Arg
- star :: CTypes -> String -> Arg
- cstar :: CTypes -> String -> Arg
- cppclass_ :: Class -> Types
- cppclass :: Class -> String -> Arg
- cppclassconst :: Class -> String -> Arg
- cppclassref_ :: Class -> Types
- cppclassref :: Class -> String -> Arg
- cppclasscopy_ :: Class -> Types
- cppclasscopy :: Class -> String -> Arg
- cppclassmove_ :: Class -> Types
- cppclassmove :: Class -> String -> Arg
- argToCTypVar :: Arg -> (CType Identity, CName Identity)
- argsToCTypVar :: [Arg] -> [(CType Identity, CName Identity)]
- argsToCTypVarNoSelf :: [Arg] -> [(CType Identity, CName Identity)]
- argToCallCExp :: Arg -> CExp Identity
- returnCType :: Types -> CType Identity
- c2Cxx :: Types -> CExp Identity -> CExp Identity
- cxx2C :: Types -> CExp Identity -> CExp Identity
- tmplAppTypeFromForm :: Form -> [CType Identity] -> CType Identity
- tmplArgToCTypVar :: IsCPrimitive -> Arg -> (CType Identity, CName Identity)
- tmplAllArgsToCTypVar :: IsCPrimitive -> Selfness -> TemplateClass -> [Arg] -> [(CType Identity, CName Identity)]
- tmplArgToCallCExp :: IsCPrimitive -> Arg -> CExp Identity
- tmplReturnCType :: IsCPrimitive -> Types -> CType Identity
- tmplMemFuncArgToCTypVar :: Class -> Arg -> (CType Identity, CName Identity)
- tmplMemFuncReturnCType :: Class -> Types -> CType Identity
- convertC2HS :: CTypes -> Type ()
- convertCpp2HS :: Maybe Class -> Types -> Type ()
- convertCpp2HS4Tmpl :: Type () -> Maybe Class -> [Type ()] -> Types -> Type ()
- hsFuncXformer :: Function -> String
- classConstraints :: Class -> Context ()
- extractArgRetTypes :: Maybe Class -> Bool -> CFunSig -> HsFunSig
- functionSignature :: Class -> Function -> Type ()
- functionSignatureT :: TemplateClass -> TemplateFunction -> Type ()
- functionSignatureTT :: TemplateClass -> TemplateFunction -> Type ()
- functionSignatureTMF :: Class -> TemplateMemberFunction -> Type ()
- tmplAccessorToTFun :: Variable -> Accessor -> TemplateFunction
- accessorCFunSig :: Types -> Accessor -> CFunSig
- accessorSignature :: Class -> Variable -> Accessor -> Type ()
- hsFFIFuncTyp :: Maybe (Selfness, Class) -> CFunSig -> Type ()
- genericFuncRet :: Function -> Types
- genericFuncArgs :: Function -> [Arg]
Documentation
HsFunSig | |
|
cppclassref_ :: Class -> Types Source #
cppclasscopy_ :: Class -> Types Source #
cppclassmove_ :: Class -> Types Source #
tmplArgToCTypVar :: IsCPrimitive -> Arg -> (CType Identity, CName Identity) Source #
tmplAllArgsToCTypVar :: IsCPrimitive -> Selfness -> TemplateClass -> [Arg] -> [(CType Identity, CName Identity)] Source #
tmplArgToCallCExp :: IsCPrimitive -> Arg -> CExp Identity Source #
tmplReturnCType :: IsCPrimitive -> Types -> CType Identity Source #
convertC2HS :: CTypes -> Type () Source #
hsFuncXformer :: Function -> String Source #
classConstraints :: Class -> Context () Source #
:: Maybe Class | class (Nothing for top-level function) |
-> Bool | is virtual function? |
-> CFunSig | C type signature information for a given function -- (Args,Types) -- ^ (argument types, return type) of a given function |
-> HsFunSig | Haskell type signature information for the function -- ([Type ()],[Asst ()]) -- ^ (types, class constraints) |
functionSignatureT :: TemplateClass -> TemplateFunction -> Type () Source #
functionSignatureTT :: TemplateClass -> TemplateFunction -> Type () Source #
functionSignatureTMF :: Class -> TemplateMemberFunction -> Type () Source #
genericFuncRet :: Function -> Types Source #
genericFuncArgs :: Function -> [Arg] Source #