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
- interface :: String -> [Module] -> 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
- 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
- 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
- fromExtName :: ExtName -> String
- 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
- exportExtName :: Export -> ExtName
- 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
- 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
- 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
- data Class
- makeClass :: Identifier -> Maybe ExtName -> [Class] -> [Ctor] -> [Method] -> Class
- classIdentifier :: Class -> Identifier
- classExtName :: Class -> ExtName
- classSuperclasses :: Class -> [Class]
- classCtors :: Class -> [Ctor]
- classDtorIsPublic :: Class -> Bool
- classMethods :: Class -> [Method]
- classConversion :: Class -> ClassConversion
- classReqs :: Class -> Reqs
- classAddCtors :: [Ctor] -> Class -> Class
- classSetDtorPrivate :: Class -> Class
- classAddMethods :: [Method] -> Class -> Class
- classIsMonomorphicSuperclass :: Class -> Bool
- classSetMonomorphicSuperclass :: Class -> Class
- classIsSubclassOfMonomorphic :: Class -> Bool
- classSetSubclassOfMonomorphic :: Class -> Class
- class HasClassyExtName a where
- data Ctor
- makeCtor :: ExtName -> [Type] -> Ctor
- mkCtor :: String -> [Type] -> Ctor
- ctorExtName :: Ctor -> ExtName
- ctorParams :: Ctor -> [Type]
- 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 -> Method
- makeFnMethod :: IsFnName Identifier name => name -> String -> MethodApplicability -> Purity -> [Type] -> Type -> Method
- mkMethod :: IsFnName String name => name -> [Type] -> Type -> Method
- mkMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> Method
- mkConstMethod :: IsFnName String name => name -> [Type] -> Type -> Method
- mkConstMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> Method
- mkStaticMethod :: IsFnName String name => name -> [Type] -> Type -> Method
- mkStaticMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> Method
- mkProps :: [[Method]] -> [Method]
- mkProp :: String -> Type -> [Method]
- mkStaticProp :: String -> Type -> [Method]
- mkBoolIsProp :: String -> [Method]
- mkBoolHasProp :: String -> [Method]
- methodImpl :: Method -> MethodImpl
- methodExtName :: Method -> ExtName
- methodApplicability :: Method -> MethodApplicability
- methodPurity :: Method -> Purity
- methodParams :: Method -> [Type]
- methodReturn :: Method -> Type
- methodConst :: Method -> Constness
- methodStatic :: Method -> Staticness
- data ClassConversion = ClassConversion {}
- data ClassConversionMode a
- classConversionNone :: ClassConversion
- classModifyConversion :: (ClassConversion -> ClassConversion) -> Class -> Class
- classSetConversion :: ClassConversion -> Class -> Class
- classSetConversionToHeap :: Class -> Class
- classSetConversionToGc :: Class -> Class
- classSetHaskellConversion :: ClassHaskellConversion -> Class -> Class
- data ClassHaskellConversion = ClassHaskellConversion {}
- data Callback
- makeCallback :: ExtName -> [Type] -> Type -> Callback
- callbackExtName :: Callback -> ExtName
- callbackParams :: Callback -> [Type]
- callbackReturn :: Callback -> Type
- callbackReqs :: Callback -> Reqs
- data Addendum = Addendum {
- addendumHaskell :: Generator ()
- class HasAddendum a
- 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
- stringOrIdentifier :: Identifier -> Maybe String -> String
- callbackToTFn :: Callback -> Type
- makeHsImportSet :: Map HsImportKey HsImportSpecs -> HsImportSet
- getHsImportSet :: HsImportSet -> Map HsImportKey HsImportSpecs
- hsImportForBits :: HsImportSet
- hsImportForInt :: HsImportSet
- hsImportForWord :: HsImportSet
- hsImportForForeign :: HsImportSet
- hsImportForForeignC :: HsImportSet
- hsImportForPrelude :: HsImportSet
- hsImportForRuntime :: HsImportSet
- hsImportForSystemPosixTypes :: HsImportSet
- hsImportForUnsafeIO :: HsImportSet
- objToHeapTWrongDirectionErrorMsg :: Maybe String -> Class -> String
- tToGcInvalidFormErrorMessage :: Maybe String -> Type -> String
- toGcTWrongDirectionErrorMsg :: Maybe String -> Type -> String
Interfaces
A complete specification of a C++ API. Generators for different languages, including the binding generator for C++, use these to produce their output.
Constructs an Interface
from the required parts. Some validation is
performed; if the resulting interface would be invalid, an error message is
returned instead.
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
.
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.
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.
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. |
exportExtName :: Export -> ExtName Source #
Returns the external name of an export.
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 type of the variable. 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.
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.
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.
Classes
A C++ class declaration. A class's external name is automatically combined
with the external names of things inside the class, by way of
HasClassyExtName
.
:: Identifier | |
-> Maybe ExtName | An optional external name; will be automatically derived from the identifier if absent. |
-> [Class] | Superclasses. |
-> [Ctor] | |
-> [Method] | |
-> 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.
classCtors :: Class -> [Ctor] Source #
The class's constructors.
classDtorIsPublic :: Class -> Bool Source #
Whether the class's destructor has public visibility.
classMethods :: Class -> [Method] Source #
The class's methods.
classConversion :: Class -> ClassConversion Source #
Behaviour for converting objects to and from foriegn values.
classSetDtorPrivate :: Class -> Class Source #
Marks a class's destructor as private, so that a binding for it won't be generated.
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.
class HasClassyExtName 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"
.
getClassyExtNameSuffix :: a -> ExtName Source #
Extracts the external name of the object, without the class name added.
getClassyExtName :: Class -> a -> ExtName Source #
Computes the external name to use in generated code, containing both the class's and object's external names.
See also toHsMethodName
.
A C++ class constructor declaration.
mkCtor name
creates a Ctor
whose external name is className_name
.
ctorExtName :: Ctor -> ExtName Source #
The constructor's external name.
ctorParams :: Ctor -> [Type] Source #
The constructor's parameter types.
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. |
-> Method |
Creates a Method
with full generality and manual name specification.
makeFnMethod :: IsFnName Identifier name => name -> String -> MethodApplicability -> Purity -> [Type] -> Type -> Method 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
.
:: IsFnName String name | |
=> name | The C++ name of the method. |
-> [Type] | Parameter types. |
-> Type | Return type. |
-> Method |
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'
.
:: IsFnName String name | |
=> name | The C++ name of the method. |
-> String | A foreign name for the method. |
-> [Type] | Parameter types. |
-> Type | Return type. |
-> Method |
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.
mkProp :: String -> Type -> [Method] Source #
Creates a getter/setter binding pair for methods:
T getFoo() const void setFoo(T)
mkStaticProp :: String -> Type -> [Method] Source #
Creates a getter/setter binding pair for static methods:
static T getFoo() const static void setFoo(T)
mkBoolIsProp :: String -> [Method] Source #
Creates a getter/setter binding pair for boolean methods, where the getter
is prefixed with is
:
bool isFoo() const void setFoo(bool)
mkBoolHasProp :: String -> [Method] Source #
Creates a getter/setter binding pair for boolean methods, where the getter
is prefixed with has
:
bool hasFoo() const void setFoo(bool)
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.
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 #
When a class object is returned from a function or taken as a parameter by
value (i.e. with objT
), it will be converted
to or from a foreign (non-C++) object. Conversion may also be performed
explicitly. This data type describes how to perform those conversions. A
class may or may not support conversion, for any particular foreign language;
what is said below only applies to classes that are convertible for a
language.
When converting between a C++ value and a foreign value, a pointer to the object is passed between C++ and the foreign language. Then, for each foreign language, a binding author can provide pieces of code in that language to translate between the pointer and a foreign value (usually by invoking the FFI functions generated by Hoppy), and generated bindings will perform these conversions automatically. The code supplied to convert in each direction should leave the original object unchanged (and alive, in case of manual memory management). (Internally, during a function call in either direction, the side that creates a value is in charge of its lifetime, but this is managed by Hoppy.)
In foreign code, foreign values can be explicitly converted to new C++ (heap) objects, and C++ object pointers can be explicitly converted to foreign values, via special functions generated for the class.
ClassConversion | |
|
data ClassConversionMode a Source #
Specifies whether (and if so, how) objects of a class get converted to and from values in a specific foreign language.
ClassConversionNone | Indicates that a class is not convertible for a language. Passing
raw |
ClassConversionManual a | Indicates that a class is convertible for a language. Passing raw
|
ClassConversionToHeap | Indicates that a class is not convertible for a language.
Nevertheless, passing an object from C++ to the foreign language via a
type of |
ClassConversionToGc | Indicates that a class is not convertible for a language.
Nevertheless, passing an object from C++ to the foreign language via a
type of This should be used for value objects so that you can simply use
|
classConversionNone :: ClassConversion Source #
Encoding parameters for a class that is not encodable or decodable.
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.
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
.
classSetHaskellConversion :: ClassHaskellConversion -> Class -> Class Source #
Replaces a class's classHaskellConversion
with a given value.
data ClassHaskellConversion Source #
Controls how conversions between C++ objects and Haskell values happen in Haskell bindings.
ClassHaskellConversion | |
|
Callbacks
A non-C++ function that can be invoked via a C++ functor.
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.
callbackReqs :: Callback -> Reqs Source #
Requirements for the callback.
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 Source #
A typeclass for types that have an addendum.
getAddendum, (setAddendum | modifyAddendum)
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
stringOrIdentifier :: Identifier -> Maybe String -> String Source #
Like extNameOrIdentifier
, but works with strings rather than ExtName
s.
callbackToTFn :: Callback -> Type Source #
Creates a fnT
from a callback's parameter
and return types.
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
.
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
.
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
.
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++.