hoppy-generator-0.7.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

Documentation

type ErrorMsg = String Source #

Indicates strings that are error messages.

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.

Interface does not have a HandlesExceptions instance because modifyExceptionHandlers does not work for it (handled exceptions cannot be modified after an Interface is constructed).

Instances
Show Interface Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

newtype InterfaceOptions Source #

Optional parameters when constructing an Interface with interface.

defaultInterfaceOptions :: InterfaceOptions Source #

Options used by interface. This contains no exception handlers.

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.

This function passes defaultInterfaceOptions to interface'.

interface' Source #

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

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 :: HasCallStack => Module -> Interface -> Interface Source #

Sets an interface's exception support module, for interfaces that use exceptions.

interfaceSetSharedPtr :: String -> Reqs -> Interface -> Interface Source #

Installs a custom std::shared_ptr implementation for use by an interface. Hoppy uses shared pointers for generated callback code. This function is useful for building code with compilers that don't provide a conforming std::shared_ptr implementation.

interfaceSetSharedPtr ident reqs iface modifies iface to use as a shared_ptr class the C++ identifier ident, which needs reqs in order to be accessed. ident should be the name of a template to which an arbitrary <T> can be appended, for example "std::shared_ptr".

A shared_ptr<T> implementation foo must at least provide the following interface:

foo();  // Initialization with a null pointer.
foo(T*);  // Initialization with a given pointer.
foo(const foo&);  // Copy-construction.
T& operator*() const;  // Dereferencing (when non-null).
T* operator->() const;  // Dereferencing and invocation (when non-null).
explicit operator bool() const;  // Is the target object null?

interfaceCompiler :: Interface -> Maybe SomeCompiler Source #

The compiler to use when building code for the interface. This can be overridden or disabled. This defaults to defaultCompiler.

interfaceSetCompiler :: Compiler a => a -> Interface -> Interface Source #

Replaces the default compiler used by the interface.

interfaceSetCompiler c = interfaceSetCompiler' (SomeCompiler c)

interfaceSetCompiler' :: Maybe SomeCompiler -> Interface -> Interface Source #

Replaces the default compiler used by the interface. When given Nothing, the interface will not be allowed to compile any code when it generates bindings.

interfaceSetNoCompiler :: Interface -> Interface Source #

Sets an interface to never compile C++ code during binding generation.

This sets the interface to have no compiler, and also asks the interface not to do things that require a compiler, which would otherwise cause a runtime failure: currently just validation of provided enum numeric types (interfaceSetValidateEnumTypes False).

interfaceValidateEnumTypes :: Interface -> Bool Source #

Whether to validate manually-provided enum numeric types (enumNumericType) using a compiled C++ sizeof(), as is done for enums that don't have an enumNumericType set.

This defaults to true, but can be set to false to discourage requiring a compiler. See interfaceSetNoCompiler.

interfaceSetValidateEnumTypes :: Bool -> Interface -> Interface Source #

Controls whether the interface will validate manually specified enum types (enumNumericType) by compiling a C++ program.

See interfaceValidateEnumTypes.

interfaceHooks :: Interface -> Hooks Source #

Hooks allowing the interface to execute code at various points during the code generator's execution. This defaults to defaultHooks.

interfaceModifyHooks :: (Hooks -> Hooks) -> Interface -> Interface Source #

Modifies the hooks associated with an interface.

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 (via the HasReqs Module instance). 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.

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.

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

Instances
Show Reqs Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

showsPrec :: Int -> Reqs -> ShowS #

show :: Reqs -> String #

showList :: [Reqs] -> ShowS #

Semigroup Reqs Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

(<>) :: Reqs -> Reqs -> Reqs #

sconcat :: NonEmpty Reqs -> Reqs #

stimes :: Integral b => b -> Reqs -> Reqs #

Monoid Reqs Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

mempty :: Reqs #

mappend :: Reqs -> Reqs -> Reqs #

mconcat :: [Reqs] -> Reqs #

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 #

Contains the data types for bindings to C++ entities: Function, Class, etc. Use addReqs or addReqIncludes to specify requirements for these entities, e.g. header files that must be included in order to access the underlying entities that are being bound.

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.

Instances
HasReqs Class Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Class

HasReqs Export Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

HasReqs Module Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

HasReqs Callback Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Callback

HasReqs CppEnum Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Enum

HasReqs Function Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Function

HasReqs Variable Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Variable

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

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 :: HasCallStack => String -> ExtName Source #

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

extNameOrIdentifier :: HasCallStack => Identifier -> Maybe ExtName -> ExtName Source #

Generates an ExtName from an Identifier, if the given name is absent.

extNameOrFnIdentifier :: HasCallStack => FnName Identifier -> Maybe ExtName -> ExtName Source #

Generates an ExtName from an FnName Identifier, if the given name is absent.

extNameOrString :: String -> Maybe ExtName -> ExtName Source #

Generates an ExtName from a string, if the given name is absent.

isValidExtName :: String -> Bool Source #

Returns true if the given string is represents a valid ExtName.

fromExtName :: ExtName -> String Source #

Returns the string an an ExtName contains.

class HasExtNames a where Source #

Types that have an external name, and also optionally have nested entities with external names as well. See getAllExtNames.

Minimal complete definition

getPrimaryExtName

Methods

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.

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 # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

toFnName :: FnName t -> FnName t Source #

Eq name => Eq (FnName name) Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

(==) :: FnName name -> FnName name -> Bool #

(/=) :: FnName name -> FnName name -> Bool #

Ord name => Ord (FnName name) Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

compare :: FnName name -> FnName name -> Ordering #

(<) :: FnName name -> FnName name -> Bool #

(<=) :: FnName name -> FnName name -> Bool #

(>) :: FnName name -> FnName name -> Bool #

(>=) :: FnName name -> FnName name -> Bool #

max :: FnName name -> FnName name -> FnName name #

min :: FnName name -> FnName name -> FnName name #

Show name => Show (FnName name) Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

showsPrec :: Int -> FnName name -> ShowS #

show :: FnName name -> String #

showList :: [FnName name] -> ShowS #

class IsFnName t a where Source #

Enables implementing automatic conversions to a FnName t.

Methods

toFnName :: a -> FnName t Source #

Instances
IsFnName t Operator Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

IsFnName t t Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

toFnName :: t -> FnName t Source #

IsFnName t (FnName t) Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

toFnName :: FnName t -> FnName t Source #

data Operator Source #

Overloadable C++ operators.

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 :: HasCallStack => 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 :: HasCallStack => Operator -> OperatorType Source #

Returns the type of an operator.

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

The Monoid instance inserts a :: between joined identifiers. Usually an identifier needs to contain at least one part, so mempty is an invalid argument to many functions in Hoppy, but it is useful as a base case for appending.

makeIdentifier :: [IdPart] -> Identifier Source #

Creates an identifier from a collection of IdParts, with ::s between.

identifierParts :: Identifier -> [IdPart] Source #

The separate parts of the identifier, between ::s.

data IdPart Source #

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

Instances
Eq IdPart Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

(==) :: IdPart -> IdPart -> Bool #

(/=) :: IdPart -> IdPart -> Bool #

Show IdPart Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

makeIdPart :: String -> Maybe [Type] -> IdPart Source #

Creates an object representing one component of an identifier.

idPartBase :: IdPart -> String Source #

The name within the enclosing scope.

idPartArgs :: IdPart -> Maybe [Type] Source #

Template arguments, if present.

ident :: String -> Identifier Source #

Creates a identifier of the form a, without any namespace operators (::).

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

Exports

class (HasAddendum a, HasExtNames a, HasReqs a, Typeable a, Show a) => Exportable a where Source #

Instances of this typeclass are C++ entities that Hoppy can expose to foreign languages: functions, classes, global variables, etc. Interfaces are largely composed of exports (grouped into modules). Hoppy uses this interface to perform code generation for each entity.

Minimal complete definition

sayExportCpp, sayExportHaskell

Methods

toExport :: a -> Export Source #

Wraps an exportable object in an existential data type.

The default instance is just toExport = Export, which does not need to be overridden in general.

castExport :: (Typeable a, Exportable b, Typeable b) => a -> Maybe b Source #

Attempts to cast an exportable object to a specific type, pulling off Export wrappers as necessary.

The default castExport = cast is fine.

sayExportCpp :: SayExportMode -> a -> Generator () Source #

Generates the C++ side of the binding for an entity.

For an entity, Hoppy invokes this function once with SayHeader when generating the header file for a module, and once with SaySource when generating the corresponding source file.

sayExportHaskell :: SayExportMode -> a -> Generator () Source #

Generates the Haskell side of the binding for an entity.

For an entity, Hoppy invokes this function once with SayExportForeignImports when it is time to emit foreign imports, and once with SayExportDecls when it is time to generate Haskell binding code later in the module. Hoppy may also call the function with SayExportBoot, if necessary.

See SayExportMode.

getExportEnumInfo :: a -> Maybe EnumInfo Source #

If the export is backed by an C++ enum, then this returns known structural information about the enum. This provides information to the "evaluate enums" hook so that Hoppy can determine enum values on its own.

By default, this returns Nothing.

See Hooks.

getExportExceptionClass :: a -> Maybe Class Source #

If the export is backed by a C++ class that is marked as supporting exceptions, then this returns the class definition.

By default, this returns Nothing.

Instances
Exportable Class Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Class

Exportable Export Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Exportable Callback Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Callback

Exportable CppEnum Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Enum

Exportable Function Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Function

Exportable Variable Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Variable

Basic types

data Type Source #

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.

Instances
Eq Type Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Show Type Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

IsParameter Type Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

normalizeType :: Type -> Type Source #

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

stripConst :: Type -> Type Source #

Strips leading Internal_TConsts off of a type.

data Scoped Source #

Indicates whether an entity is scoped or unscoped.

This is used to distinguish unscoped enums (enum) or scoped ones (enum class or enum struct).

Constructors

Unscoped

Indicates an unscoped entity (e.g. an enum).

Scoped

Indicates a scoped entity (e.g. an enum).

Instances
Eq Scoped Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

(==) :: Scoped -> Scoped -> Bool #

(/=) :: Scoped -> Scoped -> Bool #

Ord Scoped Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Show Scoped Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

isScoped :: Scoped -> Bool Source #

Returns true if a Scoped value is scoped, and false if it is unscoped.

Functions and parameters

constNegate :: Constness -> Constness Source #

Returns the opposite constness value.

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.

Instances
Eq Purity Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

Methods

(==) :: Purity -> Purity -> Bool #

(/=) :: Purity -> Purity -> Bool #

Show Purity Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

data Parameter Source #

A parameter to a function, including a type and an optional name. A name can be conveniently associated with a type with the (~:) operator.

Two Parameters are equal if their types are equal.

parameterType :: Parameter -> Type Source #

The parameter's data type.

parameterName :: Parameter -> Maybe String Source #

An optional variable name to describe the parameter. This name should follow the same rules as ExtName for its contents.

class Show a => IsParameter a where Source #

Objects that can be coerced to function parameter definitions.

Methods

toParameter :: a -> Parameter Source #

toParameters :: IsParameter a => [a] -> [Parameter] Source #

Converts a list of parameter-like objects to parameters.

np :: [Parameter] Source #

An empty parameter list. This should be used instead of a literal [] when declaring an empty parameter list, because in the context of IsParameter a => [a], the empty list is ambiguously typed, even though it doesn't matter which instance is selected.

(~:) :: IsParameter a => String -> a -> Parameter infixr 0 Source #

Associates a name string with a type to create a Parameter that can be given as a function or method parameter, instead of a raw Type. The name given here will be included as documentation in the generated code.

An empty string given for the name means not to associate a name with the parameter. This is useful to leave some parameters unnamed in a parameter list while naming other parameters, since the list must either contain all Types or all Parameters.

Conversions

data ConversionMethod c Source #

Defines the process for converting a value in one direction between C++ and a foreign language. The type parameter varies depending on the actual conversion being defined.

Constructors

ConversionUnsupported

The conversion is unsupported. If part of an interface depends on performing this conversion, code generation will fail.

BinaryCompatible

The input value and its corresponding output have the same binary representation in memory, and require no explicit conversion. Numeric types may use this conversion method.

CustomConversion c

Conversion requires a custom process as specified by the argument.

TODO Split into pure (let) vs nonpure (<-)?

data ConversionSpec Source #

The root data type for specifying how conversions happen between C++ and foreign values.

The Cpp component of this data structure specifies a C++ type, and conversions between it and something that can be marshalled over a C FFI layer, if such a conversion is possible in each direction.

Each foreign language has its own component that must be specified in order for types using this specification to be usable in that language.

makeConversionSpec Source #

Creates a ConversionSpec from an identifying name and a specification of the C++ conversion behaviour. By default, no foreign language conversion behaviour is configured. For Haskell, this should be done by using makeConversionSpecHaskell to specify behaviour, then writing that to the conversionSpecHaskell field of the ConversionSpec returned here.

data ConversionSpecCpp Source #

For a ConversionSpec, defines the C++ type and conversions to and from a C FFI layer.

Prefer makeConversionSpecCpp to using this data constructor directly.

conversionSpecCppName specifies the C++ type of the conversion. This will be the type that is passed over the C FFI as well, unless conversionSpecCppConversionType overrides it. conversionSpecCppConversionToCppExpr and conversionSpecCppConversionFromCppExpr may define custom code generation for passing values over the FFI.

Constructors

ConversionSpecCpp 

Fields

  • conversionSpecCppName :: String

    The name of the C++ type. May identify a primitive C++ type such as "unsigned int", or a more complex type like std::list<std::string>.

  • conversionSpecCppReqs :: Generator Reqs

    Computes requirements to refer to the C++ type. Being in the generator monad, this may use its environment, but should not emit code or Reqs to the generator directly.

  • conversionSpecCppConversionType :: Generator (Maybe Type)

    Specifies the type that will be passed over the C FFI.

    If absent (default), then the type named by conversionSpecCppName is also used for marshalling to foreign languages.

    If present, this represents a type distinct from conversionSpecCppName that will be exchanged across the FFI boundary. In this case, you may also want to define one or both of conversionSpecCppConversionToCppExpr and conversionSpecCppConversionFromCppExpr.

    This is a monadic value so that it has access to the generator's environment. The action should not add imports or emit code.

  • conversionSpecCppConversionToCppExpr :: Maybe (Generator () -> Maybe (Generator ()) -> Generator ())

    This controls behaviour for receiving a value passed into C++ over the FFI. Specifically, this powers the ConversionSpec being used as Function arguments and Callback return values.

    When absent (default), generated code assumes that it can implicitly convert a value passed over the FFI from the C FFI type (see conversionSpecCppConversionType) to the C++ type (i.e. conversionSpecCppName). When the former is absent, this is always fine.

    When present, this provides custom conversion behaviour for receiving a value passed into C++ over the FFI. The function should generate C++ code to convert a value from the type passed over the C FFI into the actual C++ type.

    This is a function of the form:

    \emitFromExpr maybeEmitToVar -> ...

    If the function's second argument is present, then the function should emit a variable declaration for that name, created from the expression emitted by the first argument.

    If the function's second argument is absent, then the function should emit an expression that converts the expression emitted by the first argument into the appropriate type.

    In both cases, the first generator argument should only be evaluated once by the resulting C++ expression; it is not guaranteed to be pure.

  • conversionSpecCppConversionFromCppExpr :: Maybe (Generator () -> Maybe (Generator ()) -> Generator ())

    This is the opposite of conversionSpecCppConversionToCppExpr. This being present enables custom conversion behaviour for passing a value out of C++ through the FFI. This powers the ConversionSpec being used as Function return values and Callback arguments.

makeConversionSpecCpp :: String -> Generator Reqs -> ConversionSpecCpp Source #

Builds a ConversionSpecCpp with a C++ type, with no conversions defined.

data ConversionSpecHaskell Source #

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

Prefer makeConversionSpecHaskell to using this data constructor directly.

Constructors

ConversionSpecHaskell 

Fields

Exceptions

newtype ExceptionId Source #

Each exception class has a unique exception ID.

Constructors

ExceptionId 

Fields

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.

Constructors

CatchClass Class

Indicates that instances of the given class are handled (including derived types).

CatchAll

Indicates that all C++ exceptions are handled, i.e. catch (...).

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

Constructors

ExceptionHandlers 

Fields

handleExceptions :: HandlesExceptions a => [ExceptionHandler] -> a -> a Source #

Appends additional exception handlers to an object.

Addenda

newtype 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

class HasAddendum a where Source #

A typeclass for types that have an addendum.

Minimal complete definition

getAddendum, (setAddendum | modifyAddendum)

Methods

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.

Instances
HasAddendum Class Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Class

HasAddendum Export Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

HasAddendum Module Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Base

HasAddendum Callback Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Callback

HasAddendum CppEnum Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Enum

HasAddendum Function Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Function

HasAddendum Variable Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Variable

addAddendumHaskell :: HasAddendum a => Generator () -> a -> a Source #

Adds a Haskell addendum to an object.

Enum support

data EnumInfo Source #

Structural information about a C++ enum. This is used when Hoppy is evaluating enum data, see getExportEnumInfo.

See CppEnum.

Constructors

EnumInfo 

Fields

type EnumEntryWords = [String] Source #

A list of words that comprise the name of an enum entry. Each string in this list is treated as a distinct word for the purpose of performing case conversion to create identifiers in foreign languages. These values are most easily created from a C++ identifier using splitIntoWords.

data EnumValueMap Source #

Describes the entries in a C++ enum.

Equality is defined as having the same enumValueMapValues.

Constructors

EnumValueMap 

Fields

data EnumValue Source #

Describes the value of an entry in a C++ enum. A numeric value may either be provided manually, or if omitted, Hoppy can determine it automatically.

Constructors

EnumValueManual Integer

A manually specified numeric enum value.

EnumValueAuto Identifier

A numeric enum value that will be determined when the generator is run, by means of compiling a C++ program.

Languages

type WithForeignLanguageOverrides = WithOverrides ForeignLanguage Source #

A value that may be overridden based on a ForeignLanguage.

type MapWithForeignLanguageOverrides = MapWithOverrides ForeignLanguage Source #

A map whose values may be overridden based on a ForeignLanguage.

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

data EvaluatedEnumData Source #

Information about the enum that has been completed beyond what the interface definition provides, possibly by building actual C++ code.

Constructors

EvaluatedEnumData 

Fields

type EvaluatedEnumValueMap = Map [String] Integer Source #

Contains the numeric values for each of the entries in a C++ enum.

interfaceAllExceptionClasses :: Interface -> [Class] Source #

Returns all of the exception classes in an interface.

interfaceSharedPtr :: Interface -> (Reqs, String) Source #

The name of the shared_ptr class to use, and the requirements to use it. This defaults to using std::shared_ptr from <memory>, but can be changed if necessary via interfaceSetSharedPtr.

interfaceEvaluatedEnumData :: Interface -> Maybe (Map ExtName EvaluatedEnumData) Source #

Evaluated numeric types and values for all enums in the interface.

interfaceGetEvaluatedEnumData :: HasCallStack => Interface -> ExtName -> EvaluatedEnumData Source #

Returns the map containing the calculated values for all entries in the enum with the given ExtName. This requires hooks to have been run.

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.

hsImportForMap :: HsImportSet Source #

Imports Data.Map qualified as HoppyDM.

hsImportForPrelude :: HsImportSet Source #

Imports Prelude qualified as HoppyP.

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 copy objects to the heap when being passed out of C++. Lifetimes of the resulting objects must be managed by code in the foreign language.

Calling this on a class makes objT behave like objToHeapT for values being passed out of C++.

classSetConversionToGc :: Class -> Class Source #

Modifies a class's ClassConversion structure by setting all languages that support garbage collection to copy objects to the heap when being passed out of C++, and put those objects under the care of the foreign language's garbage collector.

Calling this on a class makes objT behave like toGcT for values being passed out of C++.