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

Safe HaskellNone
LanguageHaskell2010

Foreign.Hoppy.Generator.Spec.Class

Contents

Description

Interface for defining bindings to C++ classes.

Synopsis

Data type

data Class Source #

A C++ class declaration. See IsClassEntity for more information about the interaction between a class's names and the names of entities within the class.

Use this data type's HasReqs instance to make the class accessible. You do not need to add requirements for methods' parameter or return types.

Instances
Eq Class Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Class

Methods

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

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

Ord Class Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Class

Methods

compare :: Class -> Class -> Ordering #

(<) :: Class -> Class -> Bool #

(<=) :: Class -> Class -> Bool #

(>) :: Class -> Class -> Bool #

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

max :: Class -> Class -> Class #

min :: Class -> Class -> Class #

Show Class Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Class

Methods

showsPrec :: Int -> Class -> ShowS #

show :: Class -> String #

showList :: [Class] -> ShowS #

HasAddendum Class Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Class

Exportable Class Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Class

HasExtNames Class Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Class

HasReqs Class Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Spec.Class

Construction

makeClass Source #

Arguments

:: Identifier 
-> Maybe ExtName

An optional external name; will be automatically derived from the identifier if absent by dropping leading namespaces, and taking the last component (sans template arguments).

-> [Class]

Superclasses.

-> [ClassEntity] 
-> Class 

Creates a binding for a C++ class and its contents.

Properties

Common

classExtName :: Class -> ExtName Source #

The class's external name.

classIdentifier :: Class -> Identifier Source #

The identifier used to refer to the class.

classReqs :: Class -> Reqs Source #

Requirements for bindings to access this class.

classAddendum :: Class -> Addendum Source #

The class's addendum.

Class hierarchy

classSuperclasses :: Class -> [Class] Source #

The class's public superclasses.

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.

Entities

classEntities :: Class -> [ClassEntity] Source #

The class's entities.

classAddEntities :: [ClassEntity] -> Class -> Class Source #

Adds constructors to a class.

classVariables :: Class -> [ClassVariable] Source #

Returns all of the class's variables.

classCtors :: Class -> [Ctor] Source #

Returns all of the class's constructors.

classMethods :: Class -> [Method] Source #

Returns all of the class's methods, including methods generated from Props.

classEntityPrefix :: Class -> String Source #

The prefix applied to the external names of entities (methods, etc.) within this class when determining the names of foreign languages' corresponding bindings. This defaults to the external name of the class, plus an underscore. Changing this allows you to potentially have entities with the same foreign name in separate modules. This may be the empty string, in which case the foreign name will simply be the external name of the entity.

This does not affect the things' external names themselves; external names must still be unique in an interface. For instance, a method with external name bar in a class with external name Flab and prefix Flob_ will use the effective external name Flab_bar, but the generated name in say Haskell would be Flob_bar.

See IsClassEntity and classSetEntityPrefix.

classSetEntityPrefix :: String -> Class -> Class Source #

Sets the prefix applied to foreign languages' entities generated from methods, etc. within the class.

See IsClassEntity and classEntityPrefix.

classDtorIsPublic :: Class -> Bool Source #

The class's methods.

classSetDtorPrivate :: Class -> Class Source #

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

classConversion :: Class -> ClassConversion Source #

Behaviour for converting objects to and from foriegn values.

classIsException :: Class -> Bool Source #

Whether to support using the class as a C++ exception.

classMakeException :: Class -> Class Source #

Marks a class as being used as an exception. This makes the class throwable and catchable.

Entity types

data ClassEntity Source #

A C++ entity that belongs to a class.

class IsClassEntity a where Source #

Things that live inside of a class, and have the class's external name prepended to their own in generated code. With an external name of "bar" and a class with external name "foo", the resulting name will be "foo_bar".

See classEntityPrefix and classSetEntityPrefix.

Methods

classEntityExtNameSuffix :: a -> ExtName Source #

Extracts the external name of the object, without the class name added.

classEntityExtName :: IsClassEntity a => Class -> a -> ExtName Source #

Computes the external name to use in generated code, containing both the class's and object's external names. This is the concatenation of the class's and entity's external names, separated by an underscore.

classEntityExtNames :: Class -> ClassEntity -> [ExtName] Source #

Returns all of the names in a ClassEntity within the corresponding Class.

classEntityForeignName :: IsClassEntity a => Class -> a -> ExtName Source #

Computes the name under which a class entity is to be exposed in foreign languages. This is the concatenation of a class's entity prefix, and the external name of the entity.

classEntityForeignName' :: Class -> ExtName -> ExtName Source #

Computes the name under which a class entity is to be exposed in foreign languages, given a class and an entity's external name. The result is the concatenation of a class's entity prefix, and the external name of the entity.

Class variables

Construction

makeClassVariable :: String -> Maybe ExtName -> Type -> Staticness -> Bool -> ClassEntity Source #

Creates a ClassVariable with full generality and manual name specification.

The result is wrapped in a CEVar. For an unwrapped value, use makeClassVariable_.

mkClassVariable :: String -> Type -> ClassEntity Source #

Creates a ClassVariable for a nonstatic class variable for class::varName whose external name is class_varName.

The result is wrapped in a CEVar. For an unwrapped value, use mkClassVariable_.

mkStaticClassVariable :: String -> Type -> ClassEntity Source #

Same as mkClassVariable, but returns a static variable instead.

The result is wrapped in a CEVar. For an unwrapped value, use mkStaticClassVariable_.

Constructors

Construction

makeCtor :: IsParameter p => ExtName -> [p] -> ClassEntity Source #

Creates a Ctor with full generality.

The result is wrapped in a CECtor. For an unwrapped value, use makeCtor_.

makeCtor_ :: IsParameter p => ExtName -> [p] -> Ctor Source #

The unwrapped version of makeCtor.

mkCtor :: IsParameter p => String -> [p] -> ClassEntity Source #

mkCtor name creates a Ctor whose external name is className_name.

The result is wrapped in a CECtor. For an unwrapped value, use makeCtor_.

mkCtor_ :: IsParameter p => String -> [p] -> Ctor Source #

The unwrapped version of mkCtor.

Properties

ctorExtName :: Ctor -> ExtName Source #

The constructor's external name.

ctorParams :: Ctor -> [Parameter] Source #

The constructor's parameters.

ctorExceptionHandlers :: Ctor -> ExceptionHandlers Source #

Exceptions that the constructor may throw.

Methods (member functions)

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.

Construction

makeMethod Source #

Arguments

:: (IsFnName String name, IsParameter p) 
=> name

The C++ name of the method.

-> ExtName

The external name of the method.

-> MethodApplicability 
-> Purity 
-> [p]

Parameter types.

-> Type

Return type.

-> ClassEntity 

Creates a Method with full generality and manual name specification.

The result is wrapped in a CEMethod. For an unwrapped value, use makeMethod_.

makeMethod_ :: (IsFnName String name, IsParameter p) => name -> ExtName -> MethodApplicability -> Purity -> [p] -> Type -> Method Source #

The unwrapped version of makeMethod.

makeFnMethod :: (IsFnName Identifier name, IsParameter p) => name -> String -> MethodApplicability -> Purity -> [p] -> Type -> ClassEntity Source #

Creates a Method that is in fact backed by a C++ non-member function (a la makeFn), but appears to be a regular method. This is useful for wrapping a method on the C++ side when its arguments aren't right for binding directly.

A this pointer parameter is not automatically added to the parameter list for non-static methods created with makeFnMethod.

The result is wrapped in a CEMethod. For an unwrapped value, use makeFnMethod_.

makeFnMethod_ :: (IsFnName Identifier name, IsParameter p) => name -> String -> MethodApplicability -> Purity -> [p] -> Type -> Method Source #

The unwrapped version of makeFnMethod.

mkMethod Source #

Arguments

:: (IsFnName String name, IsParameter p) 
=> name

The C++ name of the method.

-> [p]

Parameter types.

-> Type

Return type.

-> ClassEntity 

Creates a nonconst, nonstatic Method for class::methodName and whose external name is class_methodName. If the name is an operator, then the operatorPreferredExtName will be used in the external name.

For creating multiple bindings to a method, see mkMethod'.

The result is wrapped in a CEMethod. For an unwrapped value, use mkMethod_.

mkMethod_ :: (IsFnName String name, IsParameter p) => name -> [p] -> Type -> Method Source #

The unwrapped version of mkMethod.

mkMethod' Source #

Arguments

:: (IsFnName String name, IsParameter p) 
=> name

The C++ name of the method.

-> String

A foreign name for the method.

-> [p]

Parameter types.

-> Type

Return type.

-> ClassEntity 

Creates a nonconst, nonstatic Method for method class::methodName and whose external name is class_methodName. This enables multiple 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.

The result is wrapped in a CEMethod. For an unwrapped value, use mkMethod'_.

mkMethod'_ :: (IsFnName String name, IsParameter p) => name -> String -> [p] -> Type -> Method Source #

The unwrapped version of mkMethod'.

mkConstMethod :: (IsFnName String name, IsParameter p) => name -> [p] -> Type -> ClassEntity Source #

Same as mkMethod, but returns an MConst method.

The result is wrapped in a CEMethod. For an unwrapped value, use mkConstMethod_.

mkConstMethod_ :: (IsFnName String name, IsParameter p) => name -> [p] -> Type -> Method Source #

The unwrapped version of mkConstMethod.

mkConstMethod' :: (IsFnName String name, IsParameter p) => name -> String -> [p] -> Type -> ClassEntity Source #

Same as mkMethod', but returns an MConst method.

The result is wrapped in a CEMethod. For an unwrapped value, use mkConstMethod'_.

mkConstMethod'_ :: (IsFnName String name, IsParameter p) => name -> String -> [p] -> Type -> Method Source #

The unwrapped version of mkConstMethod'.

mkStaticMethod :: (IsFnName String name, IsParameter p) => name -> [p] -> Type -> ClassEntity Source #

Same as mkMethod, but returns an MStatic method.

The result is wrapped in a CEMethod. For an unwrapped value, use mkStaticMethod_.

mkStaticMethod_ :: (IsFnName String name, IsParameter p) => name -> [p] -> Type -> Method Source #

The unwrapped version of mkStaticMethod.

mkStaticMethod' :: (IsFnName String name, IsParameter p) => name -> String -> [p] -> Type -> ClassEntity Source #

Same as mkMethod', but returns an MStatic method.

The result is wrapped in a CEMethod. For an unwrapped value, use mkStaticMethod'_.

mkStaticMethod'_ :: (IsFnName String name, IsParameter p) => name -> String -> [p] -> Type -> Method Source #

The unwrapped version of mkStaticMethod'.

Properties

methodExtName :: Method -> ExtName Source #

The method's external name.

methodImpl :: Method -> MethodImpl Source #

The underlying code that the binding calls.

methodApplicability :: Method -> MethodApplicability Source #

How the method is associated to its class.

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.

methodPurity :: Method -> Purity Source #

Whether the method is pure.

methodParams :: Method -> [Parameter] Source #

The method's parameters.

methodReturn :: Method -> Type Source #

The method's return type.

methodExceptionHandlers :: Method -> ExceptionHandlers Source #

Exceptions that the method might throw.

Class properties (getter/setter pairs)

data Prop Source #

A "property" getter/setter pair.

Construction

mkProp :: String -> Type -> ClassEntity Source #

Creates a getter/setter binding pair for methods:

T foo() const
void setFoo(T)

The result is wrapped in a CEProp. For an unwrapped value, use mkProp_.

mkProp_ :: String -> Type -> Prop Source #

The unwrapped version of mkProp.

mkStaticProp :: String -> Type -> ClassEntity Source #

Creates a getter/setter binding pair for static methods:

static T foo() const
static void setFoo(T)

mkStaticProp_ :: String -> Type -> Prop Source #

The unwrapped version of mkStaticProp.

mkBoolIsProp :: String -> ClassEntity Source #

Creates a getter/setter binding pair for boolean methods, where the getter is prefixed with is:

bool isFoo() const
void setFoo(bool)

The result is wrapped in a CEProp. For an unwrapped value, use mkBoolIsProp_.

mkBoolIsProp_ :: String -> Prop Source #

The unwrapped version of mkBoolIsProp.

mkBoolHasProp :: String -> ClassEntity Source #

Creates a getter/setter binding pair for boolean methods, where the getter is prefixed with has:

bool hasFoo() const
void setFoo(bool)

The result is wrapped in a CEProp. For an unwrapped value, use mkBoolHasProp_.

mkBoolHasProp_ :: String -> Prop Source #

The unwrapped version of mkBoolHasProp.

Conversions

data ClassConversion Source #

Separately from passing object handles between C++ and foreign languages, objects can also be made to implicitly convert to native values in foreign languages. A single such type may be associated with any C++ class for each foreign language. The foreign type and the conversion process in each direction are specified using this object. Converting a C++ object to a foreign value is also called decoding, and vice versa is called encoding. A class may be convertible in one direction and not the other.

To use these implicit conversions, instead of specifying an object handle type such as ptrT . objT or refT . objT, use objT directly.

The subfields in this object specify how to do conversions between C++ and foreign languages.

Constructors

ClassConversion 

Fields

classConversionNone :: ClassConversion Source #

Conversion behaviour for a class that is not convertible.

classModifyConversion :: HasCallStack => (ClassConversion -> ClassConversion) -> Class -> Class Source #

Modifies a class's ClassConversion structure with a given function.

classSetConversion :: ClassConversion -> Class -> Class Source #

Replaces a class's ClassConversion structure.

data ClassHaskellConversion Source #

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

Constructors

ClassHaskellConversion 

Fields

Haskell generator

Names

toHsValueClassName :: Class -> Generator String Source #

The name for the typeclass of types that can be represented as values of the given C++ class.

toHsValueClassName' :: Class -> String Source #

Pure version of toHsValueClassName that doesn't create a qualified name.

toHsWithValuePtrName :: Class -> Generator String Source #

The name of the method within the toHsValueClassName typeclass for accessing an object of the type as a pointer.

toHsWithValuePtrName' :: Class -> String Source #

Pure version of toHsWithValuePtrName that doesn't create a qualified name.

toHsPtrClassName :: Constness -> Class -> Generator String Source #

The name for the typeclass of types that are (possibly const) pointers to objects of the given C++ class, or subclasses.

toHsPtrClassName' :: Constness -> Class -> String Source #

Pure version of toHsPtrClassName that doesn't create a qualified name.

toHsCastMethodName :: Constness -> Class -> Generator String Source #

The name of the function that upcasts pointers to the specific class type and constness.

toHsCastMethodName' :: Constness -> Class -> String Source #

Pure version of toHsCastMethodName that doesn't create a qualified name.

toHsDownCastClassName :: Constness -> Class -> Generator String Source #

The name of the typeclass that provides a method to downcast to a specific class type. See toHsDownCastMethodName.

toHsDownCastClassName' :: Constness -> Class -> String Source #

Pure version of toHsDownCastClassName that doesn't create a qualified name.

toHsDownCastMethodName :: Constness -> Class -> Generator String Source #

The name of the function that downcasts pointers to the specific class type and constness.

toHsDownCastMethodName' :: Constness -> Class -> String Source #

Pure version of toHsDownCastMethodName that doesn't create a qualified name.

toHsCastPrimitiveName :: Class -> Class -> Class -> Generator String Source #

The import name for the foreign function that casts between two specific pointer types. Used for upcasting and downcasting.

We need to know which module the cast function resides in, and while we could look this up, the caller always knows, so we just have them pass it in.

toHsCastPrimitiveName' :: Class -> Class -> String Source #

Pure version of toHsCastPrimitiveName that doesn't create a qualified name.

toHsConstCastFnName :: Constness -> Class -> Generator String Source #

The name of one of the functions that addremove const tofrom a class's pointer type. Given Const, it will return the function that adds const, and given Nonconst, it will return the function that removes const.

toHsConstCastFnName' :: Constness -> Class -> String Source #

Pure version of toHsConstCastFnName that doesn't create a qualified name.

toHsDataTypeName :: Constness -> Class -> Generator String Source #

The name of the data type that represents a pointer to an object of the given class and constness.

toHsDataTypeName' :: Constness -> Class -> String Source #

Pure version of toHsDataTypeName that doesn't create a qualified name.

toHsDataCtorName :: Managed -> Constness -> Class -> Generator String Source #

The name of a data constructor for one of the object pointer types.

toHsDataCtorName' :: Managed -> Constness -> Class -> String Source #

Pure version of toHsDataCtorName that doesn't create a qualified name.

toHsClassDeleteFnName' :: Class -> String Source #

The name of the foreign function import wrapping delete for the given class type. This is in internal to the binding; normal users should use delete.

This is internal to a generated Haskell module, so it does not have a public (qualified) form.

toHsClassDeleteFnPtrName' :: Class -> String Source #

The name of the foreign import that imports the same function as toHsClassDeleteFnName', but as a FunPtr rather than an actual function.

This is internal to a generated Haskell module, so it does not have a public (qualified) form.

toHsCtorName :: Class -> Ctor -> Generator String Source #

Returns the name of the Haskell function that invokes the given constructor.

toHsCtorName' :: Class -> Ctor -> String Source #

Pure version of toHsCtorName that doesn't create a qualified name.

toHsMethodName :: Class -> Method -> Generator String Source #

Returns the name of the Haskell function that invokes the given method.

toHsMethodName' :: Class -> Method -> String Source #

Pure version of toHsMethodName that doesn't create a qualified name.

toHsClassEntityName :: IsFnName String name => Class -> name -> Generator String Source #

Returns the name of the Haskell function for an entity in a class.

toHsClassEntityName' :: IsFnName String name => Class -> name -> String Source #

Pure version of toHsClassEntityName that doesn't create a qualified name.

Internal

classFindCopyCtor :: Class -> Maybe Ctor Source #

Searches a class for a copy constructor, returning it if found.

sayCppExportVar Source #

Arguments

:: Type

The type that the variable holds.

-> Maybe (Type, Type)

Nothing if the variable is not a class variable. If it is, then the first type is the generated getter's argument type for the object, and the second is the generated setter's argument type. For a class cls, this can be:

Just ('ptrT' $ 'constT' $ 'objT' cls, 'ptrT' $ 'objT' cls)
-> Bool

Whether to generate a getter. Passing false here is useful when a variable's type can't be sensibly converted to a foreign language's value.

-> ExtName

An external name from which to generate a getter function name.

-> ExtName

An external name from which to generate a setter function name.

-> Generator ()

A C++ generator that emits the variable name.

-> Generator () 

Generates C++ gateway functions (via sayCppExportFn) for getting and setting a variable (possibly a class variable).

sayHsExportVar Source #

Arguments

:: SayExportMode

The phase of code generation.

-> Type

The type that the variable holds.

-> Maybe Class

The type of the class holding the variable, if generating code for a class variable.

-> Bool

Whether to generate a getter. Passing false here is useful when a variable's type can't be sensibly converted to a foreign language's value.

-> ExtName

An external name for the getter.

-> ExtName

A foreign external name for the getter. See sayHsExportFn.

-> ExtName

An external name for the setter.

-> ExtName

A foreign external name for the setter. See sayHsExportFn.

-> Generator () 

Generates Haskell gateway functions (via sayHsExportFn) for getting and setting a variable (possibly a class variable).