Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data CFunSig = CFunSig {}
- data HsFunSig = HsFunSig {
- hsSigTypes :: [Type ()]
- hsSigConstraints :: [Asst ()]
- cvarToStr :: CTypes -> IsConst -> String -> String
- ctypToStr :: CTypes -> IsConst -> String
- 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 -> (Types, String)
- voidp :: String -> (Types, String)
- cstring :: String -> (Types, String)
- cint :: String -> (Types, String)
- int :: String -> (Types, String)
- uint :: String -> (Types, String)
- long :: String -> (Types, String)
- ulong :: String -> (Types, String)
- clong :: String -> (Types, String)
- culong :: String -> (Types, String)
- cchar :: String -> (Types, String)
- char :: String -> (Types, String)
- cshort :: String -> (Types, String)
- short :: String -> (Types, String)
- cdouble :: String -> (Types, String)
- double :: String -> (Types, String)
- doublep :: String -> (Types, String)
- cfloat :: String -> (Types, String)
- float :: String -> (Types, String)
- bool :: String -> (Types, String)
- intp :: String -> (Types, String)
- intref :: String -> (Types, String)
- charpp :: String -> (Types, String)
- ref :: CTypes -> String -> (Types, String)
- star :: CTypes -> String -> (Types, String)
- cstar :: CTypes -> String -> (Types, String)
- cppclass_ :: Class -> Types
- cppclass :: Class -> String -> (Types, String)
- cppclassconst :: Class -> String -> (Types, String)
- cppclassref_ :: Class -> Types
- cppclassref :: Class -> String -> (Types, String)
- cppclasscopy_ :: Class -> Types
- cppclasscopy :: Class -> String -> (Types, String)
- cppclassmove_ :: Class -> Types
- cppclassmove :: Class -> String -> (Types, String)
- argToString :: (Types, String) -> String
- argsToString :: Args -> String
- argsToStringNoSelf :: Args -> String
- argToCallString :: (Types, String) -> String
- argsToCallString :: Args -> String
- rettypeToString :: Types -> String
- castC2Cpp :: Types -> String -> String
- castCpp2C :: Types -> String -> String
- tmplArgToString :: Bool -> TemplateClass -> (Types, String) -> String
- tmplAllArgsToString :: Bool -> Selfness -> TemplateClass -> Args -> String
- tmplArgToCallString :: Bool -> (Types, String) -> String
- tmplAllArgsToCallString :: Bool -> Args -> String
- tmplRetTypeToString :: Bool -> Types -> String
- tmplMemFuncArgToString :: Class -> (Types, String) -> String
- tmplMemFuncRetTypeToString :: Class -> Types -> String
- 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 ()
- accessorCFunSig :: Types -> Accessor -> CFunSig
- accessorSignature :: Class -> Variable -> Accessor -> Type ()
- hsFFIFuncTyp :: Maybe (Selfness, Class) -> CFunSig -> Type ()
- genericFuncRet :: Function -> Types
- genericFuncArgs :: Function -> Args
Documentation
HsFunSig | |
|
cppclassref_ :: Class -> Types Source #
cppclasscopy_ :: Class -> Types Source #
cppclassmove_ :: Class -> Types Source #
argsToString :: Args -> String Source #
argsToStringNoSelf :: Args -> String Source #
argsToCallString :: Args -> String Source #
rettypeToString :: Types -> String Source #
tmplArgToString :: Bool -> TemplateClass -> (Types, String) -> String Source #
tmplAllArgsToString :: Bool -> Selfness -> TemplateClass -> Args -> String 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 -> Args Source #