hoppy-generator-0.1.0: C++ FFI generator - Code generator

Safe HaskellNone
LanguageHaskell2010

Foreign.Hoppy.Generator.Spec

Contents

Description

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.

Synopsis

Interfaces

data Interface Source

A complete specification of a C++ API. Generators for different languages, including the binding generator for C++, use these to produce their output.

Instances

type ErrorMsg = String Source

Indicates strings that are error messages.

interface Source

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, intercalate "." on the list produces a Haskell module name. Defaults to 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

data Include Source

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

data Module Source

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.

moduleExports :: Module -> Map ExtName Export Source

All of the exports in a module.

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.

makeModule Source

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

data Reqs Source

A set of requirements of needed to use an identifier in C++ (function, type, etc.), via a set of Includes. The monoid instance has mempty as an empty set of includes, and mappend unions two include sets.

reqsIncludes :: Reqs -> Set Include Source

The includes specified by a Reqs.

reqInclude :: Include -> Reqs Source

Creates a Reqs that contains the given include.

class HasReqs a where Source

C++ types that have requirements in order to use them in generated bindings.

Minimal complete definition

getReqs, (setReqs | modifyReqs)

Methods

getReqs :: a -> Reqs Source

Returns an object's requirements.

setReqs :: Reqs -> a -> a Source

Replaces an object's requirements with new ones.

modifyReqs :: (Reqs -> Reqs) -> a -> a Source

Modifies an object's requirements.

addReqs :: HasReqs a => Reqs -> a -> a Source

Adds to a object's requirements.

addReqIncludes :: HasReqs a => [Include] -> a -> a Source

Adds a list of includes to the requirements of an object.

Names and exports

data ExtName Source

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 Operators 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.

toExtName :: String -> ExtName Source

Creates an ExtName that contains the given string, erroring if the string is an invalid ExtName.

fromExtName :: ExtName -> String Source

Returns the string an an ExtName contains.

data FnName name Source

The C++ name of a function or method.

Constructors

FnName name

A regular, "alphanumeric" name. The exact type depends on what kind of object is being named.

FnOp Operator

An operator name.

Instances

IsFnName t (FnName t) Source 
Eq name => Eq (FnName name) Source 
Ord name => Ord (FnName name) Source 
Show name => Show (FnName name) Source 

class IsFnName t a where Source

Enables implementing automatic conversions to a FnName t.

Methods

toFnName :: a -> FnName t Source

data OperatorType Source

The arity and syntax of an operator.

Constructors

UnaryPrefixOperator String

Prefix unary operators. Examples: !x, *x, ++x.

UnaryPostfixOperator String

Postfix unary operators. Examples: x--, x++.

BinaryOperator String

Infix binary operators. Examples: x * y, x >>= y.

CallOperator

x(...) with arbitrary arity.

ArrayOperator

x[y], a binary operator with non-infix syntax.

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.

data Export Source

Specifies some C++ object (function or class) to give access to.

Constructors

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.

Instances

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.

data IdPart Source

A single component of an Identifier, between ::s.

idPartBase :: IdPart -> String Source

The name within the enclosing scope.

idPartArgs :: IdPart -> Maybe [Type] Source

Template arguments, if present.

ident :: String -> Identifier Source

Creates an identifier of the form a.

ident' :: [String] -> Identifier Source

Creates an identifier of the form a1::a2::...::aN.

ident1 :: String -> String -> Identifier Source

Creates an identifier of the form a::b.

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 -> [Type] -> Identifier Source

Creates an identifier of the form a<...>.

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

data Type Source

Concrete C++ types. It is possible to represent invalid C++ types with this, but we try to catch these and fail cleanly as much as possible.

Constructors

TVoid

C++ void, Haskell ().

TBool

C++ bool, Haskell Bool.

TChar

C++ char, Haskell CChar.

TUChar

C++ unsigned char, Haskell CUChar.

TShort

C++ short int, Haskell CShort.

TUShort

C++ unsigned short int, Haskell CUShort.

TInt

C++ int, Haskell CInt.

TUInt

C++ unsigned int, Haskell CUInt.

TLong

C++ long int, Haskell CLong.

TULong

C++ unsigned long int, Haskell CULong.

TLLong

C++ long long int, Haskell CLLong.

TULLong

C++ unsigned long long int, Haskell CULLong.

TFloat

C++ float, Haskell CFloat.

TDouble

C++ double, Haskell CDouble.

TInt8

C++ int8_t, Haskell Int8.

TInt16

C++ int16_t, Haskell Int16.

TInt32

C++ int32_t, Haskell Int32.

TInt64

C++ int64_t, Haskell Int64.

TWord8

C++ uint8_t, Haskell Word8.

TWord16

C++ uint16_t, Haskell Word16.

TWord32

C++ uint32_t, Haskell Word32.

TWord64

C++ uint64_t, Haskell Word64.

TPtrdiff

C++ ptrdiff_t, Haskell CPtrdiff.

TSize

C++ size_t, Haskell CSize.

TSSize

C++ ssize_t, Haskell CSsize.

TEnum CppEnum

A C++ enum value.

TBitspace Bitspace

A C++ bitspace value.

TPtr Type

A poiner to another type.

TRef Type

A reference to another type.

TFn [Type] Type

A function taking parameters and returning a value (or TVoid). Function pointers must wrap a TFn in a TPtr.

TCallback Callback

A handle for calling foreign code from C++.

TObj Class

An instance of a class.

TObjToHeap Class

A special case of TObj that is only allowed when passing values from C++ to a foreign language. Rather than looking at the object's ClassConversion, the object will be copied to the heap, and a pointer to the new object will be passed. The object must be copy-constructable.

The foreign language owns the pointer, even for callback arguments.

TConst Type

A const version of another type.

normalizeType :: Type -> Type Source

Canonicalizes a Type without changing its meaning. Multiple nested TConsts are collapsed into a single one.

stripConst :: Type -> Type Source

Strips leading TConsts off of a type.

Variables

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 TConst to indicate that the variable is read-only.

varReqs :: Variable -> Reqs Source

Requirements for bindings to use this variable.

varIsConst :: Variable -> Bool Source

Returns whether the variable is constant, i.e. whether its type is TConst ....

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

data CppEnum Source

A C++ enum declaration. An enum should actually be enumerable (in the sense of Haskell's Enum); if it's not, consider using a Bitspace instead.

makeEnum Source

Arguments

:: Identifier

enumIdentifier

-> Maybe ExtName

An optional external name; will be automatically derived from the identifier if absent.

-> [(Int, [String])]

enumValueNames

-> 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.

enumReqs :: CppEnum -> Reqs Source

Requirements for a Type to reference this enum.

Bitspaces

data Bitspace Source

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.

makeBitspace Source

Creates a binding for a C++ bitspace.

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.

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

data Purity Source

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.

Constructors

Nonpure

Side-affects are possible.

Pure

Side-affects will not happen.

data Function Source

A C++ function declaration.

makeFn Source

Arguments

:: 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.

fnCName :: Function -> FnName Identifier Source

The identifier used to call the function.

fnExtName :: Function -> ExtName Source

The function's external name.

fnPurity :: Function -> Purity Source

Whether the function is pure.

fnParams :: Function -> [Type] Source

The function's parameter types.

fnReturn :: Function -> Type Source

The function's return type.

fnReqs :: Function -> Reqs Source

Requirements for a binding to call the function.

Classes

data Class Source

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.

makeClass Source

Arguments

:: 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.

classReqs :: Class -> Reqs Source

Requirements for a Type to reference this class.

classAddCtors :: [Ctor] -> Class -> Class Source

Adds constructors to a class.

classSetDtorPrivate :: Class -> Class Source

Marks a class's destructor as private, so that a binding for it won't be generated.

classAddMethods :: [Method] -> Class -> Class Source

Adds methods to a class.

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".

Minimal complete definition

getClassyExtNameSuffix

Methods

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.

data Ctor Source

A C++ class constructor declaration.

makeCtor Source

Arguments

:: ExtName 
-> [Type]

Parameter types.

-> Ctor 

Creates a Ctor with full generality.

mkCtor Source

Arguments

:: String 
-> [Type]

Parameter types.

-> Ctor 

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.

data Method Source

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.

Constructors

RealMethod (FnName String)

The Method is bound to an actual class method.

FnMethod (FnName Identifier)

The Method is bound to a wrapper function. When wrapping a method with another function, this is preferrable to just using a Function binding because a method will still appear to be part of the class in foreign bindings.

data MethodApplicability Source

How a method is associated to its class. A method may be static, const, or neither (a regular method).

Constructors

MNormal 
MStatic 
MConst 

data Constness Source

Whether or not a method is const.

Constructors

Nonconst 
Const 

constNegate :: Constness -> Constness Source

Returns the opposite constness value.

data Staticness Source

Whether or not a method is static.

Constructors

Nonstatic 
Static 

makeMethod Source

Arguments

:: 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.

mkMethod Source

Arguments

:: 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'.

mkMethod' Source

Arguments

:: 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 Methods 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.

mkConstMethod :: IsFnName String name => name -> [Type] -> Type -> Method Source

Same as mkMethod, but returns an MConst method.

mkConstMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> Method Source

Same as mkMethod', but returns an MConst method.

mkStaticMethod :: IsFnName String name => name -> [Type] -> Type -> Method Source

Same as mkMethod, but returns an MStatic method.

mkStaticMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> Method Source

Same as mkMethod', but returns an MStatic method.

mkProps :: [[Method]] -> [Method] Source

Used in conjunction with mkProp and friends, this creates a list of Methods for binding to getter/setter method pairs. This can be used as follows:

myClass =
  makeClass ... $
  [ methods... ] ++
  mkProps
  [ mkBoolIsProp myClass "adjustable"
  , mkProp myClass "maxWidth" TInt
  ]

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 TObj), 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.

Constructors

ClassConversion 

Fields

classHaskellConversion :: Maybe ClassHaskellConversion

Conversions to and from Haskell.

classConversionNone :: ClassConversion Source

Encoding parameters for a class that is not encodable or decodable.

classModifyConversion :: (ClassConversion -> ClassConversion) -> Class -> Class Source

Modifies classes' ClassEncoding structures with a given function.

data ClassHaskellConversion Source

Controls how conversions between C++ objects and Haskell values happen in Haskell bindings.

Constructors

ClassHaskellConversion 

Fields

classHaskellConversionType :: Generator HsType

Produces the Haskell type that represents a value of the corresponding C++ class. This generator may add imports, but must not output code or add exports.

classHaskellConversionToCppFn :: Generator ()

Produces a Haskell expression that evaluates to a function that takes an object of the type that classHaskellConversionType generates, and returns a pointer to a new non-const C++ class object in IO. The generator must output code and may add imports, but must not add exports.

classHaskellConversionFromCppFn :: Generator ()

Produces a Haskell expression that evaluates to a function that takes a pointer to a const C++ class object, and returns an object of the type that classHaskellConversionType generates, in IO. The generator must output code and may add imports, but must not add exports.

Callbacks

data Callback Source

A non-C++ function that can be invoked via a C++ functor.

makeCallback Source

Arguments

:: ExtName 
-> [Type]

Parameter types.

-> Type

Return type.

-> Callback 

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.

callbackToTFn :: Callback -> Type Source

Creates a TFn from a callback's parameter and return types.

Addenda

data Addendum Source

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).

Constructors

Addendum 

Fields

addendumHaskell :: Generator ()

Code to be output into the Haskell binding. May also add imports and exports.

class HasAddendum a Source

A typeclass for types that have an addendum.

Minimal complete definition

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 HsImportKeys may be merged.

data HsImportSpecs Source

A specification of bindings to import from a module. If Nothing, then the entire module is imported. If Just empty, then only instances are imported.

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.

Constructors

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 X (a, b, c) import.

HsImportValAll

The name is imported, along with all names underneath it. This is a X (..) import.

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.

hsImportSetMakeSource :: HsImportSet -> HsImportSet Source

Sets all of the import specifications in an import set to be {--} imports.

Internal to Hoppy

stringOrIdentifier :: Identifier -> Maybe String -> String Source

Like extNameOrIdentifier, but works with strings rather than ExtNames.

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.

hsImportForUnsafeIO :: HsImportSet Source

Imports System.IO.Unsafe qualified as HoppySIU.

Error messages

tObjToHeapWrongDirectionErrorMsg :: Maybe String -> Class -> String Source

Returns an error message indicating that TObjToHeap is used where data is going from a foreign langauge into C++.