Safe Haskell | None |
---|---|
Language | Haskell2010 |
The primary data types for specifying C++ interfaces.
Show
instances in this module produce strings of the form "<TypeOfObject
nameOfObject otherInfo...>"
. They can be used in error messages without
specifying a noun separately, i.e. write show cls
instead of "the class
" ++ show cls
.
- data Interface
- type ErrorMsg = String
- data InterfaceOptions = InterfaceOptions {}
- defaultInterfaceOptions :: InterfaceOptions
- interface :: String -> [Module] -> Either ErrorMsg Interface
- interface' :: String -> [Module] -> InterfaceOptions -> Either ErrorMsg Interface
- interfaceName :: Interface -> String
- interfaceModules :: Interface -> Map String Module
- interfaceNamesToModules :: Interface -> Map ExtName Module
- interfaceHaskellModuleBase :: Interface -> [String]
- interfaceDefaultHaskellModuleBase :: [String]
- interfaceAddHaskellModuleBase :: [String] -> Interface -> Either String Interface
- interfaceHaskellModuleImportNames :: Interface -> Map Module String
- interfaceExceptionHandlers :: Interface -> ExceptionHandlers
- interfaceCallbacksThrow :: Interface -> Bool
- interfaceSetCallbacksThrow :: Bool -> Interface -> Interface
- interfaceExceptionClassId :: Interface -> Class -> Maybe ExceptionId
- interfaceExceptionSupportModule :: Interface -> Maybe Module
- interfaceSetExceptionSupportModule :: Module -> Interface -> Interface
- data Include
- includeStd :: String -> Include
- includeLocal :: String -> Include
- includeToString :: Include -> String
- data Module
- moduleName :: Module -> String
- moduleHppPath :: Module -> String
- moduleCppPath :: Module -> String
- moduleExports :: Module -> Map ExtName Export
- moduleReqs :: Module -> Reqs
- moduleExceptionHandlers :: Module -> ExceptionHandlers
- moduleCallbacksThrow :: Module -> Maybe Bool
- moduleSetCallbacksThrow :: MonadState Module m => Maybe Bool -> m ()
- moduleAddendum :: Module -> Addendum
- moduleHaskellName :: Module -> Maybe [String]
- makeModule :: String -> String -> String -> Module
- moduleModify :: Module -> StateT Module (Either String) () -> Either ErrorMsg Module
- moduleModify' :: Module -> StateT Module (Either String) () -> Module
- moduleSetHppPath :: MonadState Module m => String -> m ()
- moduleSetCppPath :: MonadState Module m => String -> m ()
- moduleAddExports :: (MonadError String m, MonadState Module m) => [Export] -> m ()
- moduleAddHaskellName :: (MonadError String m, MonadState Module m) => [String] -> m ()
- data Reqs
- reqsIncludes :: Reqs -> Set Include
- reqInclude :: Include -> Reqs
- class HasReqs a where
- addReqs :: HasReqs a => Reqs -> a -> a
- addReqIncludes :: HasReqs a => [Include] -> a -> a
- data ExtName
- toExtName :: String -> ExtName
- isValidExtName :: String -> Bool
- fromExtName :: ExtName -> String
- class HasExtNames a where
- getAllExtNames :: HasExtNames a => a -> [ExtName]
- data FnName name
- class IsFnName t a where
- data Operator
- = OpCall
- | OpComma
- | OpAssign
- | OpArray
- | OpDeref
- | OpAddress
- | OpAdd
- | OpAddAssign
- | OpSubtract
- | OpSubtractAssign
- | OpMultiply
- | OpMultiplyAssign
- | OpDivide
- | OpDivideAssign
- | OpModulo
- | OpModuloAssign
- | OpPlus
- | OpMinus
- | OpIncPre
- | OpIncPost
- | OpDecPre
- | OpDecPost
- | OpEq
- | OpNe
- | OpLt
- | OpLe
- | OpGt
- | OpGe
- | OpNot
- | OpAnd
- | OpOr
- | OpBitNot
- | OpBitAnd
- | OpBitAndAssign
- | OpBitOr
- | OpBitOrAssign
- | OpBitXor
- | OpBitXorAssign
- | OpShl
- | OpShlAssign
- | OpShr
- | OpShrAssign
- data OperatorType
- operatorPreferredExtName :: Operator -> ExtName
- operatorPreferredExtName' :: Operator -> String
- operatorType :: Operator -> OperatorType
- data Export
- exportAddendum :: Export -> Addendum
- data Identifier
- identifierParts :: Identifier -> [IdPart]
- data IdPart
- idPartBase :: IdPart -> String
- idPartArgs :: IdPart -> Maybe [Type]
- ident :: String -> Identifier
- ident' :: [String] -> Identifier
- ident1 :: String -> String -> Identifier
- ident2 :: String -> String -> String -> Identifier
- ident3 :: String -> String -> String -> String -> Identifier
- ident4 :: String -> String -> String -> String -> String -> Identifier
- ident5 :: String -> String -> String -> String -> String -> String -> Identifier
- identT :: String -> [Type] -> Identifier
- identT' :: [(String, Maybe [Type])] -> Identifier
- ident1T :: String -> String -> [Type] -> Identifier
- ident2T :: String -> String -> String -> [Type] -> Identifier
- ident3T :: String -> String -> String -> String -> [Type] -> Identifier
- ident4T :: String -> String -> String -> String -> String -> [Type] -> Identifier
- ident5T :: String -> String -> String -> String -> String -> String -> [Type] -> Identifier
- data Type
- = Internal_TVoid
- | Internal_TBool
- | Internal_TChar
- | Internal_TUChar
- | Internal_TShort
- | Internal_TUShort
- | Internal_TInt
- | Internal_TUInt
- | Internal_TLong
- | Internal_TULong
- | Internal_TLLong
- | Internal_TULLong
- | Internal_TFloat
- | Internal_TDouble
- | Internal_TInt8
- | Internal_TInt16
- | Internal_TInt32
- | Internal_TInt64
- | Internal_TWord8
- | Internal_TWord16
- | Internal_TWord32
- | Internal_TWord64
- | Internal_TPtrdiff
- | Internal_TSize
- | Internal_TSSize
- | Internal_TEnum CppEnum
- | Internal_TBitspace Bitspace
- | Internal_TPtr Type
- | Internal_TRef Type
- | Internal_TFn [Type] Type
- | Internal_TCallback Callback
- | Internal_TObj Class
- | Internal_TObjToHeap Class
- | Internal_TToGc Type
- | Internal_TConst Type
- normalizeType :: Type -> Type
- stripConst :: Type -> Type
- data Variable
- makeVariable :: Identifier -> Maybe ExtName -> Type -> Variable
- varIdentifier :: Variable -> Identifier
- varExtName :: Variable -> ExtName
- varType :: Variable -> Type
- varReqs :: Variable -> Reqs
- varIsConst :: Variable -> Bool
- varGetterExtName :: Variable -> ExtName
- varSetterExtName :: Variable -> ExtName
- data CppEnum
- makeEnum :: Identifier -> Maybe ExtName -> [(Int, [String])] -> CppEnum
- enumIdentifier :: CppEnum -> Identifier
- enumExtName :: CppEnum -> ExtName
- enumValueNames :: CppEnum -> [(Int, [String])]
- enumReqs :: CppEnum -> Reqs
- enumValuePrefix :: CppEnum -> String
- enumSetValuePrefix :: String -> CppEnum -> CppEnum
- data Bitspace
- makeBitspace :: ExtName -> Type -> [(Int, [String])] -> Bitspace
- bitspaceExtName :: Bitspace -> ExtName
- bitspaceType :: Bitspace -> Type
- bitspaceValueNames :: Bitspace -> [(Int, [String])]
- bitspaceEnum :: Bitspace -> Maybe CppEnum
- bitspaceAddEnum :: CppEnum -> Bitspace -> Bitspace
- bitspaceCppTypeIdentifier :: Bitspace -> Maybe Identifier
- bitspaceFromCppValueFn :: Bitspace -> Maybe String
- bitspaceToCppValueFn :: Bitspace -> Maybe String
- bitspaceAddCppType :: Identifier -> Maybe String -> Maybe String -> Bitspace -> Bitspace
- bitspaceReqs :: Bitspace -> Reqs
- bitspaceValuePrefix :: Bitspace -> String
- bitspaceSetValuePrefix :: String -> Bitspace -> Bitspace
- data Purity
- data Function
- makeFn :: IsFnName Identifier name => name -> Maybe ExtName -> Purity -> [Type] -> Type -> Function
- fnCName :: Function -> FnName Identifier
- fnExtName :: Function -> ExtName
- fnPurity :: Function -> Purity
- fnParams :: Function -> [Type]
- fnReturn :: Function -> Type
- fnReqs :: Function -> Reqs
- fnExceptionHandlers :: Function -> ExceptionHandlers
- data Class
- makeClass :: Identifier -> Maybe ExtName -> [Class] -> [ClassEntity] -> Class
- classIdentifier :: Class -> Identifier
- classExtName :: Class -> ExtName
- classSuperclasses :: Class -> [Class]
- classEntities :: Class -> [ClassEntity]
- classAddEntities :: [ClassEntity] -> Class -> Class
- classVariables :: Class -> [ClassVariable]
- classCtors :: Class -> [Ctor]
- classMethods :: Class -> [Method]
- classDtorIsPublic :: Class -> Bool
- classSetDtorPrivate :: Class -> Class
- classConversion :: Class -> ClassConversion
- classReqs :: Class -> Reqs
- classEntityPrefix :: Class -> String
- classSetEntityPrefix :: String -> Class -> Class
- classIsMonomorphicSuperclass :: Class -> Bool
- classSetMonomorphicSuperclass :: Class -> Class
- classIsSubclassOfMonomorphic :: Class -> Bool
- classSetSubclassOfMonomorphic :: Class -> Class
- classIsException :: Class -> Bool
- classMakeException :: Class -> Class
- data ClassEntity
- class IsClassEntity a where
- classEntityExtName :: IsClassEntity a => Class -> a -> ExtName
- classEntityForeignName :: IsClassEntity a => Class -> a -> ExtName
- classEntityForeignName' :: Class -> ExtName -> ExtName
- data ClassVariable
- makeClassVariable :: String -> Maybe ExtName -> Type -> Staticness -> Bool -> ClassEntity
- makeClassVariable_ :: String -> Maybe ExtName -> Type -> Staticness -> Bool -> ClassVariable
- mkClassVariable :: String -> Type -> ClassEntity
- mkClassVariable_ :: String -> Type -> ClassVariable
- mkStaticClassVariable :: String -> Type -> ClassEntity
- mkStaticClassVariable_ :: String -> Type -> ClassVariable
- classVarCName :: ClassVariable -> String
- classVarExtName :: ClassVariable -> ExtName
- classVarType :: ClassVariable -> Type
- classVarStatic :: ClassVariable -> Staticness
- classVarGettable :: ClassVariable -> Bool
- classVarGetterExtName :: Class -> ClassVariable -> ExtName
- classVarGetterForeignName :: Class -> ClassVariable -> ExtName
- classVarSetterExtName :: Class -> ClassVariable -> ExtName
- classVarSetterForeignName :: Class -> ClassVariable -> ExtName
- data Ctor
- makeCtor :: ExtName -> [Type] -> ClassEntity
- makeCtor_ :: ExtName -> [Type] -> Ctor
- mkCtor :: String -> [Type] -> ClassEntity
- mkCtor_ :: String -> [Type] -> Ctor
- ctorExtName :: Ctor -> ExtName
- ctorParams :: Ctor -> [Type]
- ctorExceptionHandlers :: Ctor -> ExceptionHandlers
- data Method
- data MethodImpl
- = RealMethod (FnName String)
- | FnMethod (FnName Identifier)
- data MethodApplicability
- data Constness
- constNegate :: Constness -> Constness
- data Staticness
- makeMethod :: IsFnName String name => name -> ExtName -> MethodApplicability -> Purity -> [Type] -> Type -> ClassEntity
- makeMethod_ :: IsFnName String name => name -> ExtName -> MethodApplicability -> Purity -> [Type] -> Type -> Method
- makeFnMethod :: IsFnName Identifier name => name -> String -> MethodApplicability -> Purity -> [Type] -> Type -> ClassEntity
- makeFnMethod_ :: IsFnName Identifier name => name -> String -> MethodApplicability -> Purity -> [Type] -> Type -> Method
- mkMethod :: IsFnName String name => name -> [Type] -> Type -> ClassEntity
- mkMethod_ :: IsFnName String name => name -> [Type] -> Type -> Method
- mkMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> ClassEntity
- mkMethod'_ :: IsFnName String name => name -> String -> [Type] -> Type -> Method
- mkConstMethod :: IsFnName String name => name -> [Type] -> Type -> ClassEntity
- mkConstMethod_ :: IsFnName String name => name -> [Type] -> Type -> Method
- mkConstMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> ClassEntity
- mkConstMethod'_ :: IsFnName String name => name -> String -> [Type] -> Type -> Method
- mkStaticMethod :: IsFnName String name => name -> [Type] -> Type -> ClassEntity
- mkStaticMethod_ :: IsFnName String name => name -> [Type] -> Type -> Method
- mkStaticMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> ClassEntity
- mkStaticMethod'_ :: IsFnName String name => name -> String -> [Type] -> Type -> Method
- data Prop
- mkProp :: String -> Type -> ClassEntity
- mkProp_ :: String -> Type -> Prop
- mkStaticProp :: String -> Type -> ClassEntity
- mkStaticProp_ :: String -> Type -> Prop
- mkBoolIsProp :: String -> ClassEntity
- mkBoolIsProp_ :: String -> Prop
- mkBoolHasProp :: String -> ClassEntity
- mkBoolHasProp_ :: String -> Prop
- methodImpl :: Method -> MethodImpl
- methodExtName :: Method -> ExtName
- methodApplicability :: Method -> MethodApplicability
- methodPurity :: Method -> Purity
- methodParams :: Method -> [Type]
- methodReturn :: Method -> Type
- methodExceptionHandlers :: Method -> ExceptionHandlers
- methodConst :: Method -> Constness
- methodStatic :: Method -> Staticness
- data ClassConversion = ClassConversion {}
- classConversionNone :: ClassConversion
- classModifyConversion :: (ClassConversion -> ClassConversion) -> Class -> Class
- classSetConversion :: ClassConversion -> Class -> Class
- data ClassHaskellConversion = ClassHaskellConversion {}
- classHaskellConversionNone :: ClassHaskellConversion
- classSetHaskellConversion :: ClassHaskellConversion -> Class -> Class
- data Callback
- makeCallback :: ExtName -> [Type] -> Type -> Callback
- callbackExtName :: Callback -> ExtName
- callbackParams :: Callback -> [Type]
- callbackReturn :: Callback -> Type
- callbackThrows :: Callback -> Maybe Bool
- callbackReqs :: Callback -> Reqs
- callbackSetThrows :: Bool -> Callback -> Callback
- newtype ExceptionId = ExceptionId {}
- exceptionCatchAllId :: ExceptionId
- data ExceptionHandler
- data ExceptionHandlers = ExceptionHandlers {}
- class HandlesExceptions a where
- handleExceptions :: HandlesExceptions a => [ExceptionHandler] -> a -> a
- data Addendum = Addendum {
- addendumHaskell :: Generator ()
- class HasAddendum a where
- addAddendumHaskell :: HasAddendum a => Generator () -> a -> a
- type HsModuleName = String
- data HsImportSet
- data HsImportKey = HsImportKey {}
- data HsImportSpecs = HsImportSpecs {}
- type HsImportName = String
- data HsImportVal
- hsWholeModuleImport :: HsModuleName -> HsImportSet
- hsQualifiedImport :: HsModuleName -> HsModuleName -> HsImportSet
- hsImport1 :: HsModuleName -> HsImportName -> HsImportSet
- hsImport1' :: HsModuleName -> HsImportName -> HsImportVal -> HsImportSet
- hsImports :: HsModuleName -> [HsImportName] -> HsImportSet
- hsImports' :: HsModuleName -> [(HsImportName, HsImportVal)] -> HsImportSet
- hsImportSetMakeSource :: HsImportSet -> HsImportSet
- interfaceAllExceptionClasses :: Interface -> [Class]
- classFindCopyCtor :: Class -> Maybe Ctor
- makeHsImportSet :: Map HsImportKey HsImportSpecs -> HsImportSet
- getHsImportSet :: HsImportSet -> Map HsImportKey HsImportSpecs
- hsImportForBits :: HsImportSet
- hsImportForException :: HsImportSet
- hsImportForInt :: HsImportSet
- hsImportForWord :: HsImportSet
- hsImportForForeign :: HsImportSet
- hsImportForForeignC :: HsImportSet
- hsImportForMap :: HsImportSet
- hsImportForPrelude :: HsImportSet
- hsImportForRuntime :: HsImportSet
- hsImportForSystemPosixTypes :: HsImportSet
- hsImportForTypeable :: HsImportSet
- hsImportForUnsafeIO :: HsImportSet
- objToHeapTWrongDirectionErrorMsg :: Maybe String -> Class -> String
- tToGcInvalidFormErrorMessage :: Maybe String -> Type -> String
- toGcTWrongDirectionErrorMsg :: Maybe String -> Type -> String
- classSetConversionToHeap :: Class -> Class
- classSetConversionToGc :: Class -> Class
- module Foreign.Hoppy.Generator.Spec.ClassFeature
Interfaces
A complete specification of a C++ API. Generators for different languages, including the binding generator for C++, use these to produce their output.
Interface
does not have a HandlesExceptions
instance because
modifyExceptionHandlers
does not work for it (handled exceptions cannot be
modified after an Interface
is constructed).
data InterfaceOptions Source #
defaultInterfaceOptions :: InterfaceOptions Source #
Options used by interface
. This contains no exception handlers.
Constructs an Interface
from the required parts. Some validation is
performed; if the resulting interface would be invalid, an error message is
returned instead.
This function passes defaultInterfaceOptions
to interface'
.
Same as interface
, but accepts some optional arguments.
interfaceName :: Interface -> String Source #
The textual name of the interface.
interfaceModules :: Interface -> Map String Module Source #
All of the individual modules, by moduleName
.
interfaceNamesToModules :: Interface -> Map ExtName Module Source #
Maps each ExtName
exported by some module to the module that exports
the name.
interfaceHaskellModuleBase :: Interface -> [String] Source #
The name of the parent Haskell module under which a Haskell module will be
generated for a Hoppy Module
. This is a list of Haskell module path
components, in other words,
on the list
produces a Haskell module name. Defaults to
intercalate
"."interfaceDefaultHaskellModuleBase
, and may be overridden with
interfaceAddHaskellModuleBase
.
interfaceDefaultHaskellModuleBase :: [String] Source #
The default Haskell module under which Hoppy modules will be generated.
This is Foreign.Hoppy.Generated
, that is:
["Foreign", "Hoppy", "Generated"]
interfaceAddHaskellModuleBase :: [String] -> Interface -> Either String Interface Source #
Sets an interface to generate all of its modules under the given Haskell
module prefix. See interfaceHaskellModuleBase
.
interfaceHaskellModuleImportNames :: Interface -> Map Module String Source #
Short qualified module import names that generated modules use to refer to each other tersely.
interfaceExceptionHandlers :: Interface -> ExceptionHandlers Source #
Exceptions that all functions in the interface may throw.
interfaceCallbacksThrow :: Interface -> Bool Source #
Whether callbacks within the interface support throwing C++ exceptions
from Haskell into C++ during their execution. This may be overridden by
moduleCallbacksThrow
and callbackThrows
.
interfaceSetCallbacksThrow :: Bool -> Interface -> Interface Source #
Changes callbackThrows
for all callbacks in an interface that don't have it
set explicitly at the module or callback level.
interfaceExceptionClassId :: Interface -> Class -> Maybe ExceptionId Source #
Returns the the exception ID for a class in an interface, if it has one
(i.e. if it's been marked as an exception class with classMakeException
).
interfaceExceptionSupportModule :: Interface -> Maybe Module Source #
When an interface uses C++ exceptions, then one module needs to manually be selected to contain some interface-specific runtime support. This is the selected module.
interfaceSetExceptionSupportModule :: Module -> Interface -> Interface Source #
Sets an interface's exception support module, for interfaces that use exceptions.
C++ includes
An #include
directive in a C++ file.
includeStd :: String -> Include Source #
Creates an #include <...>
directive.
includeLocal :: String -> Include Source #
Creates an #include "..."
directive.
includeToString :: Include -> String Source #
Returns the complete #include ...
line for an include, including
trailing newline.
Modules
A portion of functionality in a C++ API. An Interface
is composed of
multiple modules. A module will generate a single compilation unit
containing bindings for all of the module's exports. The C++ code for a
generated module will #include
everything necessary for what is written to
the header and source files separately. You can declare include dependencies
with e.g. addReqIncludes
, either for individual exports or at the module
level. Dependencies between modules are handled automatically, and
circularity is supported to a certain extent. See the documentation for the
individual language modules for further details.
moduleName :: Module -> String Source #
The module's name. A module name must identify a unique module within
an Interface
.
moduleHppPath :: Module -> String Source #
A relative path under a C++ sources root to which the generator will write a header file for the module's C++ bindings.
moduleCppPath :: Module -> String Source #
A relative path under a C++ sources root to which the generator will write a source file for the module's C++ bindings.
moduleReqs :: Module -> Reqs Source #
Module-level requirements.
moduleExceptionHandlers :: Module -> ExceptionHandlers Source #
Exceptions that all functions in the module may throw.
moduleCallbacksThrow :: Module -> Maybe Bool Source #
Whether callbacks exported from the module support exceptions being
thrown during their execution. When present, this overrides
interfaceCallbacksThrow
. This maybe overridden by callbackThrows
.
moduleSetCallbacksThrow :: MonadState Module m => Maybe Bool -> m () Source #
Changes callbackThrows
for all callbacks in a module that don't have it
set explicitly.
moduleAddendum :: Module -> Addendum Source #
The module's addendum.
moduleHaskellName :: Module -> Maybe [String] Source #
The generated Haskell module name, underneath the
interfaceHaskellModuleBase
. If absent (by default), the moduleName
is used. May be modified with moduleAddHaskellName
.
Creates an empty module, ready to be configured with moduleModify
.
moduleModify :: Module -> StateT Module (Either String) () -> Either ErrorMsg Module Source #
Extends a module. To be used with the module state-monad actions in this package.
moduleModify' :: Module -> StateT Module (Either String) () -> Module Source #
Same as moduleModify
, but calls error
in the case of failure, which is
okay in for a generator which would abort in this case anyway.
moduleSetHppPath :: MonadState Module m => String -> m () Source #
Replaces a module's moduleHppPath
.
moduleSetCppPath :: MonadState Module m => String -> m () Source #
Replaces a module's moduleCppPath
.
moduleAddExports :: (MonadError String m, MonadState Module m) => [Export] -> m () Source #
Adds exports to a module. An export must only be added to any module at most once, and must not be added to multiple modules.
moduleAddHaskellName :: (MonadError String m, MonadState Module m) => [String] -> m () Source #
Changes a module's moduleHaskellName
from the default. This can only be
called once on a module.
Requirements
class HasReqs a where Source #
C++ types that have requirements in order to use them in generated bindings.
getReqs, (setReqs | modifyReqs)
addReqIncludes :: HasReqs a => [Include] -> a -> a Source #
Adds a list of includes to the requirements of an object.
Names and exports
An external name is a string that generated bindings use to uniquely
identify an object at runtime. An external name must start with an
alphabetic character, and may only contain alphanumeric characters and '_'
.
You are free to use whatever naming style you like; case conversions will be
performed automatically when required. Hoppy does make use of some
conventions though, for example with Operator
s and in the provided bindings
for the C++ standard library.
External names must be unique within an interface. They may not be reused between modules. This assumption is used for symbol naming in compiled shared objects and to freely import modules in Haskell bindings.
isValidExtName :: String -> Bool Source #
Returns true if the given string is represents a valid ExtName
.
class HasExtNames a where Source #
Types that have an external name, and also optionally have nested entities
with external names as well. See getAllExtNames
.
getPrimaryExtName :: a -> ExtName Source #
Returns the external name by which a given entity is referenced.
getNestedExtNames :: a -> [ExtName] Source #
Returns external names nested within the given entity. Does not include the primary external name.
getAllExtNames :: HasExtNames a => a -> [ExtName] Source #
Returns a list of all of the external names an entity contains. This
combines both getPrimaryExtName
and getNestedExtNames
.
The C++ name of a function or method.
Overloadable C++ operators.
OpCall | x(...) |
OpComma | x, y |
OpAssign | x = y |
OpArray | x[y] |
OpDeref | *x |
OpAddress | &x |
OpAdd | x + y |
OpAddAssign | x += y |
OpSubtract | x - y |
OpSubtractAssign | x -= y |
OpMultiply | x * y |
OpMultiplyAssign | x *= y |
OpDivide | x / y |
OpDivideAssign | x /= y |
OpModulo | x % y |
OpModuloAssign | x %= y |
OpPlus | +x |
OpMinus | -x |
OpIncPre | ++x |
OpIncPost | x++ |
OpDecPre | --x |
OpDecPost | x-- |
OpEq | x == y |
OpNe | x != y |
OpLt | x < y |
OpLe | x <= y |
OpGt | x > y |
OpGe | x >= y |
OpNot | !x |
OpAnd | x && y |
OpOr | x || y |
OpBitNot | ~x |
OpBitAnd | x & y |
OpBitAndAssign | x &= y |
OpBitOr | x | y |
OpBitOrAssign | x |= y |
OpBitXor | x ^ y |
OpBitXorAssign | x ^= y |
OpShl | x << y |
OpShlAssign | x <<= y |
OpShr | x >> y |
OpShrAssign | x >>= y |
data OperatorType Source #
The arity and syntax of an operator.
UnaryPrefixOperator String | Prefix unary operators. Examples: |
UnaryPostfixOperator String | Postfix unary operators. Examples: |
BinaryOperator String | Infix binary operators. Examples: |
CallOperator |
|
ArrayOperator |
|
operatorPreferredExtName :: Operator -> ExtName Source #
Returns a conventional string to use for the ExtName
of an operator.
operatorPreferredExtName' :: Operator -> String Source #
Returns a conventional name for an operator, as with
operatorPreferredExtName
, but as a string.
operatorType :: Operator -> OperatorType Source #
Returns the type of an operator.
Specifies some C++ object (function or class) to give access to.
ExportVariable Variable | Exports a variable. |
ExportEnum CppEnum | Exports an enum. |
ExportBitspace Bitspace | Exports a bitspace. |
ExportFn Function | Exports a function. |
ExportClass Class | Exports a class with all of its contents. |
ExportCallback Callback | Exports a callback. |
exportAddendum :: Export -> Addendum Source #
Returns the export's addendum. Export
doesn't have a HasAddendum
instance because you normally wouldn't want to modify the addendum of one.
data Identifier Source #
A path to some C++ object, including namespaces. An identifier consists of
multiple parts separated by "::"
. Each part has a name string followed
by an optional template argument list, where each argument gets rendered from
a Type
(non-type arguments for template metaprogramming are not supported).
identifierParts :: Identifier -> [IdPart] Source #
The separate parts of the identifier, between ::
s.
A single component of an Identifier
, between ::
s.
idPartBase :: IdPart -> String Source #
The name within the enclosing scope.
ident :: String -> Identifier Source #
Creates an identifier of the form a
.
ident' :: [String] -> Identifier Source #
Creates an identifier of the form a1::a2::...::aN
.
ident2 :: String -> String -> String -> Identifier Source #
Creates an identifier of the form a::b::c
.
ident3 :: String -> String -> String -> String -> Identifier Source #
Creates an identifier of the form a::b::c::d
.
ident4 :: String -> String -> String -> String -> String -> Identifier Source #
Creates an identifier of the form a::b::c::d::e
.
ident5 :: String -> String -> String -> String -> String -> String -> Identifier Source #
Creates an identifier of the form a::b::c::d::e::f
.
identT' :: [(String, Maybe [Type])] -> Identifier Source #
Creates an identifier with arbitrary many templated and non-templated parts.
ident1T :: String -> String -> [Type] -> Identifier Source #
Creates an identifier of the form a::b<...>
.
ident2T :: String -> String -> String -> [Type] -> Identifier Source #
Creates an identifier of the form a::b::c<...>
.
ident3T :: String -> String -> String -> String -> [Type] -> Identifier Source #
Creates an identifier of the form a::b::c::d<...>
.
ident4T :: String -> String -> String -> String -> String -> [Type] -> Identifier Source #
Creates an identifier of the form a::b::c::d::e<...>
.
ident5T :: String -> String -> String -> String -> String -> String -> [Type] -> Identifier Source #
Creates an identifier of the form a::b::c::d::e::f<...>
.
Basic types
A concrete C++ type. Use the bindings in Foreign.Hoppy.Generator.Types for values of this type; these data constructors are subject to change without notice.
normalizeType :: Type -> Type Source #
Canonicalizes a Type
without changing its meaning. Multiple nested
Internal_TConst
s are collapsed into a single one.
stripConst :: Type -> Type Source #
Strips leading Internal_TConst
s off of a type.
Variables
A C++ variable.
makeVariable :: Identifier -> Maybe ExtName -> Type -> Variable Source #
Creates a binding for a C++ variable.
varIdentifier :: Variable -> Identifier Source #
The identifier used to refer to the variable.
varExtName :: Variable -> ExtName Source #
The variable's external name.
varType :: Variable -> Type Source #
The variable's type. This may be
constT
to indicate that the variable is
read-only.
varIsConst :: Variable -> Bool Source #
Returns whether the variable is constant, i.e. whether its type is
.constT
...
varGetterExtName :: Variable -> ExtName Source #
Returns the external name of the getter function for the variable.
varSetterExtName :: Variable -> ExtName Source #
Returns the external name of the setter function for the variable.
Enums
:: Identifier | |
-> Maybe ExtName | An optional external name; will be automatically derived from the identifier if absent. |
-> [(Int, [String])] | |
-> CppEnum |
Creates a binding for a C++ enum.
enumIdentifier :: CppEnum -> Identifier Source #
The identifier used to refer to the enum.
enumExtName :: CppEnum -> ExtName Source #
The enum's external name.
enumValueNames :: CppEnum -> [(Int, [String])] Source #
The numeric values and names of the enum values. A single value's name is broken up into words. How the words and ext name get combined to make a name in a particular foreign language depends on the language.
enumValuePrefix :: CppEnum -> String Source #
The prefix applied to value names (enumValueNames
) when determining
the names of values in foreign languages. This defaults to the external
name of the enum, plus an underscore.
See enumSetValuePrefix
.
enumSetValuePrefix :: String -> CppEnum -> CppEnum Source #
Sets the prefix applied to the names of enum values' identifiers in foreign languages.
See enumValuePrefix
.
Bitspaces
A C++ numeric space with bitwise operations. This is similar to a
CppEnum
, but in addition to the extra operations, this differs in that
these values aren't enumerable.
Additionally, as a kludge for Qtah, a bitspace may have a C++ type
(bitspaceCppTypeIdentifier
) separate from its numeric type
(bitspaceType
). Qt bitspaces aren't raw numbers but are instead type-safe
QFlags
objects that don't implicitly convert from integers, so we need a
means to do so manually. Barring general ad-hoc argument and return value
conversion support, we allow this as follows: when given a C++ type, then a
bitspace may also have a conversion function between the numeric and C++
type, in each direction. If a conversion function is present, it will be
used for conversions in its respective direction. The C++ type is not a full
Type
, but only an Identifier
, since additional information is not needed.
See bitspaceAddCppType
.
bitspaceExtName :: Bitspace -> ExtName Source #
The bitspace's external name.
bitspaceType :: Bitspace -> Type Source #
The C++ type used for bits values. This should be a primitive numeric
type, usually intT
.
bitspaceValueNames :: Bitspace -> [(Int, [String])] Source #
The numeric values and names of the bitspace values. See
enumValueNames
.
bitspaceEnum :: Bitspace -> Maybe CppEnum Source #
An associated enum, whose values may be converted to values in the bitspace.
bitspaceAddEnum :: CppEnum -> Bitspace -> Bitspace Source #
Associates an enum with the bitspace. See bitspaceEnum
.
bitspaceCppTypeIdentifier :: Bitspace -> Maybe Identifier Source #
The optional C++ type for a bitspace.
bitspaceFromCppValueFn :: Bitspace -> Maybe String Source #
The name of a C++ function to convert from the bitspace's C++ type to
bitspaceType
.
bitspaceToCppValueFn :: Bitspace -> Maybe String Source #
The name of a C++ function to convert from bitspaceType
to the
bitspace's C++ type.
bitspaceAddCppType :: Identifier -> Maybe String -> Maybe String -> Bitspace -> Bitspace Source #
bitspaceAddCppType cppTypeIdentifier toCppValueFn fromCppValueFn
associates a C++ type (plus optional conversion functions) with a bitspace.
At least one conversion should be specified, otherwise adding the C++ type
will mean nothing. You should also add use requirements to the bitspace for
all of these arguments; see HasReqs
.
bitspaceReqs :: Bitspace -> Reqs Source #
Requirements for emitting the bindings for a bitspace, i.e. what's
necessary to reference bitspaceCppTypeIdentifier
,
bitspaceFromCppValueFn
, and bitspaceToCppValueFn
. bitspaceType
can
take some numeric types that require includes as well, but you don't need
to list these here.
bitspaceValuePrefix :: Bitspace -> String Source #
The prefix applied to value names (bitspaceValueNames
) when
determining the names of values in foreign languages. This defaults to
the external name of the bitspace, plus an underscore.
bitspaceSetValuePrefix :: String -> Bitspace -> Bitspace Source #
Sets the prefix applied to the names of enum values' identifiers in foreign languages.
See enumValuePrefix
.
Functions
Whether or not a function may cause side-effects.
Haskell bindings for pure functions will not be in IO
, and calls to pure
functions will be executed non-strictly. Calls to impure functions will
execute in the IO monad.
Member functions for mutable classes should not be made pure, because it is difficult in general to control when the call will be made.
A C++ function declaration.
:: IsFnName Identifier name | |
=> name | |
-> Maybe ExtName | An optional external name; will be automatically derived from the identifier if absent. |
-> Purity | |
-> [Type] | Parameter types. |
-> Type | Return type. |
-> Function |
Creates a binding for a C++ function.
fnExceptionHandlers :: Function -> ExceptionHandlers Source #
Exceptions that the function might throw.
Classes
A C++ class declaration. See IsClassEntity
for more information about the
interaction between a class's names and the names of entities within the
class.
:: Identifier | |
-> Maybe ExtName | An optional external name; will be automatically derived from the identifier if absent by dropping leading namespaces, and taking the last component (sans template arguments). |
-> [Class] | Superclasses. |
-> [ClassEntity] | |
-> Class |
Creates a binding for a C++ class and its contents.
classIdentifier :: Class -> Identifier Source #
The identifier used to refer to the class.
classExtName :: Class -> ExtName Source #
The class's external name.
classSuperclasses :: Class -> [Class] Source #
The class's public superclasses.
classEntities :: Class -> [ClassEntity] Source #
The class's entities.
classAddEntities :: [ClassEntity] -> Class -> Class Source #
Adds constructors to a class.
classVariables :: Class -> [ClassVariable] Source #
Returns all of the class's variables.
classCtors :: Class -> [Ctor] Source #
Returns all of the class's constructors.
classMethods :: Class -> [Method] Source #
Returns all of the class's methods, including methods generated from
Prop
s.
classDtorIsPublic :: Class -> Bool Source #
The class's methods.
classSetDtorPrivate :: Class -> Class Source #
Marks a class's destructor as private, so that a binding for it won't be generated.
classConversion :: Class -> ClassConversion Source #
Behaviour for converting objects to and from foriegn values.
classEntityPrefix :: Class -> String Source #
The prefix applied to the external names of entities (methods, etc.) within this class when determining the names of foreign languages' corresponding bindings. This defaults to the external name of the class, plus an underscore. Changing this allows you to potentially have entities with the same foreign name in separate modules. This may be the empty string, in which case the foreign name will simply be the external name of the entity.
This does not affect the things' external names themselves; external
names must still be unique in an interface. For instance, a method with
external name bar
in a class with external name Flab
and prefix
Flob_
will use the effective external name Flab_bar
, but the
generated name in say Haskell would be Flob_bar
.
See IsClassEntity
and classSetEntityPrefix
.
classSetEntityPrefix :: String -> Class -> Class Source #
Sets the prefix applied to foreign languages' entities generated from methods, etc. within the class.
See IsClassEntity
and classEntityPrefix
.
classIsMonomorphicSuperclass :: Class -> Bool Source #
This is true for classes passed through
classSetMonomorphicSuperclass
.
classSetMonomorphicSuperclass :: Class -> Class Source #
Explicitly marks a class as being monomorphic (i.e. not having any
virtual methods or destructors). By default, Hoppy assumes that a class that
is derived is also polymorphic, but it can happen that this is not the case.
Downcasting with dynamic_cast
from such classes is not available. See also
classSetSubclassOfMonomorphic
.
classIsSubclassOfMonomorphic :: Class -> Bool Source #
This is true for classes passed through
classSetSubclassOfMonomorphic
.
classSetSubclassOfMonomorphic :: Class -> Class Source #
Marks a class as being derived from some monomorphic superclass. This
prevents any downcasting to this class. Generally it is better to use
classSetMonomorphicSuperclass
on the specific superclasses that are
monomorphic, but in cases where this is not possible, this function can be
applied to the subclass instead.
classIsException :: Class -> Bool Source #
Whether to support using the class as a C++ exception.
classMakeException :: Class -> Class Source #
Marks a class as being used as an exception. This makes the class throwable and catchable.
data ClassEntity Source #
A C++ entity that belongs to a class.
class IsClassEntity a where Source #
Things that live inside of a class, and have the class's external name
prepended to their own in generated code. With an external name of "bar"
and a class with external name "foo"
, the resulting name will be
"foo_bar"
.
See classEntityPrefix
and classSetEntityPrefix
.
classEntityExtNameSuffix :: a -> ExtName Source #
Extracts the external name of the object, without the class name added.
classEntityExtName :: IsClassEntity a => Class -> a -> ExtName Source #
Computes the external name to use in generated code, containing both the class's and object's external names. This is the concatenation of the class's and entity's external names, separated by an underscore.
classEntityForeignName :: IsClassEntity a => Class -> a -> ExtName Source #
Computes the name under which a class entity is to be exposed in foreign languages. This is the concatenation of a class's entity prefix, and the external name of the entity.
classEntityForeignName' :: Class -> ExtName -> ExtName Source #
Computes the name under which a class entity is to be exposed in foreign languages, given a class and an entity's external name. The result is the concatenation of a class's entity prefix, and the external name of the entity.
data ClassVariable Source #
A C++ member variable.
makeClassVariable :: String -> Maybe ExtName -> Type -> Staticness -> Bool -> ClassEntity Source #
Creates a ClassVariable
with full generality and manual name specification.
The result is wrapped in a CEVar
. For an unwrapped value, use
makeClassVariable_
.
makeClassVariable_ :: String -> Maybe ExtName -> Type -> Staticness -> Bool -> ClassVariable Source #
The unwrapped version of makeClassVariable
.
mkClassVariable :: String -> Type -> ClassEntity Source #
Creates a ClassVariable
for a nonstatic class variable for
class::varName
whose external name is class_varName
.
The result is wrapped in a CEVar
. For an unwrapped value, use
mkClassVariable_
.
mkClassVariable_ :: String -> Type -> ClassVariable Source #
The unwrapped version of mkClassVariable
.
mkStaticClassVariable :: String -> Type -> ClassEntity Source #
Same as mkClassVariable
, but returns a static variable instead.
The result is wrapped in a CEVar
. For an unwrapped value, use
mkStaticClassVariable_
.
mkStaticClassVariable_ :: String -> Type -> ClassVariable Source #
The unwrapped version of mkStaticClassVariable
.
classVarCName :: ClassVariable -> String Source #
The variable's C++ name.
classVarExtName :: ClassVariable -> ExtName Source #
The variable's external name.
classVarType :: ClassVariable -> Type Source #
The variable's type. This may be
constT
to indicate that the variable is
read-only.
classVarStatic :: ClassVariable -> Staticness Source #
Whether the variable is static (i.e. whether it exists once in the class itself and not in each instance).
classVarGettable :: ClassVariable -> Bool Source #
Whether the variable should have an accompanying getter. Note this exists only for disabling getters on callback variables - as there is currently no functionality to pass callbacks out of c++
classVarGetterExtName :: Class -> ClassVariable -> ExtName Source #
Returns the external name of the getter function for the class variable.
classVarGetterForeignName :: Class -> ClassVariable -> ExtName Source #
Returns the foreign name of the getter function for the class variable.
classVarSetterExtName :: Class -> ClassVariable -> ExtName Source #
Returns the external name of the setter function for the class variable.
classVarSetterForeignName :: Class -> ClassVariable -> ExtName Source #
Returns the foreign name of the setter function for the class variable.
A C++ class constructor declaration.
:: ExtName | |
-> [Type] | Parameter types. |
-> ClassEntity |
:: String | |
-> [Type] | Parameter types. |
-> ClassEntity |
ctorExtName :: Ctor -> ExtName Source #
The constructor's external name.
ctorParams :: Ctor -> [Type] Source #
The constructor's parameter types.
ctorExceptionHandlers :: Ctor -> ExceptionHandlers Source #
Exceptions that the constructor may throw.
A C++ class method declaration.
Any operator function that can be written as a method may have its binding be written either as part of the associated class or as a separate entity, independently of how the function is declared in C++.
data MethodImpl Source #
The C++ code to which a Method
is bound.
RealMethod (FnName String) | The |
FnMethod (FnName Identifier) | The |
data MethodApplicability Source #
How a method is associated to its class. A method may be static, const, or neither (a regular method).
Whether or not a method is const.
constNegate :: Constness -> Constness Source #
Returns the opposite constness value.
data Staticness Source #
Whether or not a method is static.
:: IsFnName String name | |
=> name | The C++ name of the method. |
-> ExtName | The external name of the method. |
-> MethodApplicability | |
-> Purity | |
-> [Type] | Parameter types. |
-> Type | Return type. |
-> ClassEntity |
Creates a Method
with full generality and manual name specification.
The result is wrapped in a CEMethod
. For an unwrapped value, use
makeMethod_
.
makeMethod_ :: IsFnName String name => name -> ExtName -> MethodApplicability -> Purity -> [Type] -> Type -> Method Source #
The unwrapped version of makeMethod
.
makeFnMethod :: IsFnName Identifier name => name -> String -> MethodApplicability -> Purity -> [Type] -> Type -> ClassEntity Source #
Creates a Method
that is in fact backed by a C++ non-member function (a
la makeFn
), but appears to be a regular method. This is useful for
wrapping a method on the C++ side when its arguments aren't right for binding
directly.
A this
pointer parameter is not automatically added to the parameter
list for non-static methods created with makeFnMethod
.
The result is wrapped in a CEMethod
. For an unwrapped value, use
makeFnMethod_
.
makeFnMethod_ :: IsFnName Identifier name => name -> String -> MethodApplicability -> Purity -> [Type] -> Type -> Method Source #
The unwrapped version of makeFnMethod
.
:: IsFnName String name | |
=> name | The C++ name of the method. |
-> [Type] | Parameter types. |
-> Type | Return type. |
-> ClassEntity |
Creates a nonconst, nonstatic Method
for class::methodName
and whose
external name is class_methodName
. If the name is an operator, then the
operatorPreferredExtName
will be used in the external name.
For creating multiple bindings to a method, see mkMethod'
.
The result is wrapped in a CEMethod
. For an unwrapped value, use
mkMethod_
.
mkMethod_ :: IsFnName String name => name -> [Type] -> Type -> Method Source #
The unwrapped version of mkMethod
.
:: IsFnName String name | |
=> name | The C++ name of the method. |
-> String | A foreign name for the method. |
-> [Type] | Parameter types. |
-> Type | Return type. |
-> ClassEntity |
Creates a nonconst, nonstatic Method
for method class::methodName
and
whose external name is class_methodName
. This enables multiple Method
s
with different foreign names (and hence different external names) to bind to
the same method, e.g. to make use of optional arguments or overloading. See
mkMethod
for a simpler form.
The result is wrapped in a CEMethod
. For an unwrapped value, use
mkMethod'_
.
mkMethod'_ :: IsFnName String name => name -> String -> [Type] -> Type -> Method Source #
The unwrapped version of mkMethod'
.
mkConstMethod :: IsFnName String name => name -> [Type] -> Type -> ClassEntity Source #
Same as mkMethod
, but returns an MConst
method.
The result is wrapped in a CEMethod
. For an unwrapped value, use
mkConstMethod_
.
mkConstMethod_ :: IsFnName String name => name -> [Type] -> Type -> Method Source #
The unwrapped version of mkConstMethod
.
mkConstMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> ClassEntity Source #
Same as mkMethod'
, but returns an MConst
method.
The result is wrapped in a CEMethod
. For an unwrapped value, use
mkConstMethod'_
.
mkConstMethod'_ :: IsFnName String name => name -> String -> [Type] -> Type -> Method Source #
The unwrapped version of mkConstMethod'
.
mkStaticMethod :: IsFnName String name => name -> [Type] -> Type -> ClassEntity Source #
Same as mkMethod
, but returns an MStatic
method.
The result is wrapped in a CEMethod
. For an unwrapped value, use
mkStaticMethod_
.
mkStaticMethod_ :: IsFnName String name => name -> [Type] -> Type -> Method Source #
The unwrapped version of mkStaticMethod
.
mkStaticMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> ClassEntity Source #
Same as mkMethod'
, but returns an MStatic
method.
The result is wrapped in a CEMethod
. For an unwrapped value, use
mkStaticMethod'_
.
mkStaticMethod'_ :: IsFnName String name => name -> String -> [Type] -> Type -> Method Source #
The unwrapped version of mkStaticMethod'
.
mkStaticProp :: String -> Type -> ClassEntity Source #
Creates a getter/setter binding pair for static methods:
static T foo() const static void setFoo(T)
mkStaticProp_ :: String -> Type -> Prop Source #
The unwrapped version of mkStaticProp
.
mkBoolIsProp :: String -> ClassEntity Source #
Creates a getter/setter binding pair for boolean methods, where the getter
is prefixed with is
:
bool isFoo() const void setFoo(bool)
The result is wrapped in a CEProp
. For an unwrapped value, use
mkBoolIsProp_
.
mkBoolIsProp_ :: String -> Prop Source #
The unwrapped version of mkBoolIsProp
.
mkBoolHasProp :: String -> ClassEntity Source #
Creates a getter/setter binding pair for boolean methods, where the getter
is prefixed with has
:
bool hasFoo() const void setFoo(bool)
The result is wrapped in a CEProp
. For an unwrapped value, use
mkBoolHasProp_
.
mkBoolHasProp_ :: String -> Prop Source #
The unwrapped version of mkBoolHasProp
.
methodImpl :: Method -> MethodImpl Source #
The underlying code that the binding calls.
methodExtName :: Method -> ExtName Source #
The method's external name.
methodApplicability :: Method -> MethodApplicability Source #
How the method is associated to its class.
methodPurity :: Method -> Purity Source #
Whether the method is pure.
methodParams :: Method -> [Type] Source #
The method's parameter types.
methodReturn :: Method -> Type Source #
The method's return type.
methodExceptionHandlers :: Method -> ExceptionHandlers Source #
Exceptions that the method might throw.
methodConst :: Method -> Constness Source #
Returns the constness of a method, based on its methodApplicability
.
methodStatic :: Method -> Staticness Source #
Returns the staticness of a method, based on its methodApplicability
.
Conversion to and from foreign values
data ClassConversion Source #
Separately from passing object handles between C++ and foreign languages, objects can also be made to implicitly convert to native values in foreign languages. A single such type may be associated with any C++ class for each foreign language. The foreign type and the conversion process in each direction are specified using this object. Converting a C++ object to a foreign value is also called decoding, and vice versa is called encoding. A class may be convertible in one direction and not the other.
To use these implicit conversions, instead of specifying an object handle
type such as
or
ptrT
. objT
,
use refT
. objT
objT
directly.
The subfields in this object specify how to do conversions between C++ and foreign languages.
ClassConversion | |
|
classConversionNone :: ClassConversion Source #
Conversion behaviour for a class that is not convertible.
classModifyConversion :: (ClassConversion -> ClassConversion) -> Class -> Class Source #
Modifies a class's ClassConversion
structure with a given function.
classSetConversion :: ClassConversion -> Class -> Class Source #
Replaces a class's ClassConversion
structure.
data ClassHaskellConversion Source #
Controls how conversions between C++ objects and Haskell values happen in Haskell bindings.
ClassHaskellConversion | |
|
classHaskellConversionNone :: ClassHaskellConversion Source #
Conversion behaviour for a class that is not convertible to or from Haskell.
classSetHaskellConversion :: ClassHaskellConversion -> Class -> Class Source #
Replaces a class's classHaskellConversion
with a given value.
Callbacks
A non-C++ function that can be invoked via a C++ functor or function pointer.
Creates a binding for constructing callbacks into foreign code.
callbackExtName :: Callback -> ExtName Source #
The callback's external name.
callbackParams :: Callback -> [Type] Source #
The callback's parameter types.
callbackReturn :: Callback -> Type Source #
The callback's return type.
callbackThrows :: Callback -> Maybe Bool Source #
Whether the callback supports throwing C++ exceptions from Haskell into
C++ during its execution. When absent, the value is inherited from
moduleCallbacksThrow
and interfaceCallbacksThrow
.
callbackReqs :: Callback -> Reqs Source #
Requirements for the callback.
callbackSetThrows :: Bool -> Callback -> Callback Source #
Sets whether a callback supports handling thrown C++ exceptions and passing them into C++.
Exceptions
newtype ExceptionId Source #
Each exception class has a unique exception ID.
ExceptionId | |
|
exceptionCatchAllId :: ExceptionId Source #
The exception ID that represents the catch-all type.
data ExceptionHandler Source #
Indicates the ability to handle a certain type of C++ exception.
CatchClass Class | Indicates that instances of the given class are handled (including derived types). |
CatchAll | Indicates that all C++ exceptions are handled, i.e. |
data ExceptionHandlers Source #
Represents a list of exception handlers to be used for a body of code.
Order is important; a CatchAll
will prevent all subsequent handlers from
being invoked.
ExceptionHandlers | |
|
class HandlesExceptions a where Source #
Types that can handle exceptions.
getExceptionHandlers, modifyExceptionHandlers
getExceptionHandlers :: a -> ExceptionHandlers Source #
Extracts the exception handlers for an object.
handleExceptions :: HandlesExceptions a => [ExceptionHandler] -> a -> a Source #
Appends additional exception handlers to an object.
Addenda
A literal piece of code that will be inserted into a generated source file
after the regular binding glue. The Monoid
instance concatenates code
(actions).
Addendum | |
|
class HasAddendum a where Source #
A typeclass for types that have an addendum.
getAddendum :: a -> Addendum Source #
Returns an object's addendum.
setAddendum :: Addendum -> a -> a Source #
Replaces and object's addendum with another.
modifyAddendum :: (Addendum -> Addendum) -> a -> a Source #
Modified an object's addendum.
addAddendumHaskell :: HasAddendum a => Generator () -> a -> a Source #
Adds a Haskell addendum to an object.
Haskell imports
type HsModuleName = String Source #
A Haskell module name.
data HsImportSet Source #
A collection of imports for a Haskell module. This is a monoid: import Statements are merged to give the union of imported bindings.
This structure supports two specific types of imports:
- import Foo (...)
- import qualified Foo as Bar
Imports with as
but without qualified
, and qualified
imports with a
spec list, are not supported. This satisfies the needs of the code
generator, and keeps the merging logic simple.
data HsImportKey Source #
References an occurrence of an import statement, under which bindings can
be imported. Only imported specs under equal HsImportKey
s may be merged.
data HsImportSpecs Source #
type HsImportName = String Source #
An identifier that can be imported from a module. Symbols may be used here
when surrounded by parentheses. Examples are "fmap"
and "(++)"
.
data HsImportVal Source #
Specifies how a name is imported.
HsImportVal | The name is imported, and nothing underneath it is. |
HsImportValSome [HsImportName] | The name is imported, as are specific names underneath it. This is a
|
HsImportValAll | The name is imported, along with all names underneath it. This is a |
hsWholeModuleImport :: HsModuleName -> HsImportSet Source #
An import for the entire contents of a Haskell module.
hsQualifiedImport :: HsModuleName -> HsModuleName -> HsImportSet Source #
A qualified import of a Haskell module.
hsImport1 :: HsModuleName -> HsImportName -> HsImportSet Source #
An import of a single name from a Haskell module.
hsImport1' :: HsModuleName -> HsImportName -> HsImportVal -> HsImportSet Source #
A detailed import of a single name from a Haskell module.
hsImports :: HsModuleName -> [HsImportName] -> HsImportSet Source #
An import of multiple names from a Haskell module.
hsImports' :: HsModuleName -> [(HsImportName, HsImportVal)] -> HsImportSet Source #
A detailed import of multiple names from a Haskell module.
Internal to Hoppy
interfaceAllExceptionClasses :: Interface -> [Class] Source #
Returns all of the exception classes in an interface.
classFindCopyCtor :: Class -> Maybe Ctor Source #
Searches a class for a copy constructor, returning it if found.
Haskell imports
makeHsImportSet :: Map HsImportKey HsImportSpecs -> HsImportSet Source #
Constructor for an import set.
getHsImportSet :: HsImportSet -> Map HsImportKey HsImportSpecs Source #
Returns the import set's internal map from module names to imported bindings.
hsImportForBits :: HsImportSet Source #
Imports Data.Bits qualified as HoppyDB
.
hsImportForException :: HsImportSet Source #
Imports Control.Exception qualified as HoppyCE
.
hsImportForInt :: HsImportSet Source #
Imports Data.Int qualified as HoppyDI
.
hsImportForWord :: HsImportSet Source #
Imports Data.Word qualified as HoppyDW
.
hsImportForForeign :: HsImportSet Source #
Imports Foreign qualified as HoppyF
.
hsImportForForeignC :: HsImportSet Source #
Imports Foreign.C qualified as HoppyFC
.
hsImportForMap :: HsImportSet Source #
Imports Data.Map qualified as HoppyDM
.
hsImportForPrelude :: HsImportSet Source #
Imports Prelude qualified as HoppyP
.
hsImportForRuntime :: HsImportSet Source #
Imports Foreign.Hoppy.Runtime qualified as HoppyFHR
.
hsImportForSystemPosixTypes :: HsImportSet Source #
Imports System.Posix.Types qualified as HoppySPT
.
hsImportForTypeable :: HsImportSet Source #
Imports Data.Typeable qualified as HoppyDT
.
hsImportForUnsafeIO :: HsImportSet Source #
Imports System.IO.Unsafe qualified as HoppySIU
.
Error messages
objToHeapTWrongDirectionErrorMsg :: Maybe String -> Class -> String Source #
Returns an error message indicating that
objToHeapT
is used where data is going from a
foreign language into C++.
tToGcInvalidFormErrorMessage :: Maybe String -> Type -> String Source #
Returns an error message indicating that
objToHeapT
is used where data is going from a
foreign language into C++.
toGcTWrongDirectionErrorMsg :: Maybe String -> Type -> String Source #
Returns an error message indicating that
toGcT
is used where data is going from a
foreign language into C++.
Advanced class conversions
classSetConversionToHeap :: Class -> Class Source #
Modifies a class's ClassConversion
structure by setting all languages
to use ClassConversionToHeap
.
classSetConversionToGc :: Class -> Class Source #
Modifies a class's ClassConversion
structure by setting all languages
that support garbage collection to use ClassConversionToGc
.