-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | C++ FFI generator - Code generator -- -- Hoppy generates Haskell bindings to C++ libraries. -- -- This package is the code generator. @package hoppy-generator @version 0.5.0 -- | Concrete C++ types. It is possible to represent invalid C++ types with -- these functions, but we try to catch these and fail cleanly as much as -- possible. module Foreign.Hoppy.Generator.Types -- | C++ void, Haskell (). voidT :: Type -- | C++ bool, Haskell Bool. boolT :: Type -- | C++ char, Haskell CChar. charT :: Type -- | C++ unsigned char, Haskell CUChar. ucharT :: Type -- | C++ short int, Haskell CShort. shortT :: Type -- | C++ unsigned short int, Haskell CUShort. ushortT :: Type -- | C++ int, Haskell CInt. intT :: Type -- | C++ unsigned int, Haskell CUInt. uintT :: Type -- | C++ long int, Haskell CLong. longT :: Type -- | C++ unsigned long int, Haskell CULong. ulongT :: Type -- | C++ long long int, Haskell CLLong. llongT :: Type -- | C++ unsigned long long int, Haskell CULLong. ullongT :: Type -- | C++ float, Haskell CFloat. floatT :: Type -- | C++ double, Haskell CDouble. doubleT :: Type -- | C++ int8_t, Haskell Int8. int8T :: Type -- | C++ int16_t, Haskell Int16. int16T :: Type -- | C++ int32_t, Haskell Int32. int32T :: Type -- | C++ int64_t, Haskell Int64. int64T :: Type -- | C++ uint8_t, Haskell Word8. word8T :: Type -- | C++ uint16_t, Haskell Word16. word16T :: Type -- | C++ uint32_t, Haskell Word32. word32T :: Type -- | C++ uint64_t, Haskell Word64. word64T :: Type -- | C++ ptrdiff_t, Haskell CPtrdiff. ptrdiffT :: Type -- | C++ size_t, Haskell CSize. sizeT :: Type -- | C++ ssize_t, Haskell CSsize. ssizeT :: Type -- | A C++ enum value. enumT :: CppEnum -> Type -- | A C++ bitspace value. bitspaceT :: Bitspace -> Type -- | A pointer to another type. ptrT :: Type -> Type -- | A reference to another type. refT :: Type -> Type -- | A function taking parameters and returning a value (or voidT). -- Function pointers must wrap a fnT in a ptrT. fnT :: [Type] -> Type -> Type -- | A handle for calling foreign code from C++. callbackT :: Callback -> Type -- | An instance of a class. When used in a parameter or return type and -- not wrapped in a ptrT or refT, this is a by-value -- object. objT :: Class -> Type -- | A special case of objT that is only allowed when passing -- objects 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 heap object will be passed. The object must -- be copy-constructable. -- -- The foreign language owns the pointer, even for callback -- arguments. objToHeapT :: Class -> Type -- | This type transfers ownership of the object to the foreign language's -- garbage collector, and results in a managed pointer in the foreign -- language. This may only be used in one of the forms below, when -- passing data from C++ to a foreign language (i.e. in a C++ function -- return type or in a callback argument). In the first case, the -- temporary object is copied to the heap, and the result is a managed -- pointer to the heap object instead of the temporary. -- -- toGcT :: Type -> Type -- | A const version of another type. constT :: Type -> Type -- | Bindings for common class operations, such as copy construction. module Foreign.Hoppy.Generator.Spec.ClassFeature -- | Sets of functionality that can be stamped onto a class with -- classAddFeatures. data ClassFeature -- | Provides the assignment operator, Foo& Foo::operator=(const -- Foo&). Assignable :: ClassFeature -- | Provides operators <, <=, >, -- >=, for example bool Foo::operator<(const -- Foo&). This feature does not automatically include -- Equatable. Comparable :: ClassFeature -- | Provides copy construction, Foo::Foo(const Foo&). Copyable :: ClassFeature -- | Provides operator== and operator!=, for example -- bool Foo::operator==(const Foo&). Equatable :: ClassFeature -- | Adds the contents of a feature to a class. Does not check for overlap -- with existing class contents. classAddFeatures :: [ClassFeature] -> Class -> Class instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.ClassFeature.ClassFeature instance GHC.Classes.Eq Foreign.Hoppy.Generator.Spec.ClassFeature.ClassFeature -- | Shared portion of the Haskell code generator. Usable by binding -- definitions. module Foreign.Hoppy.Generator.Language.Haskell -- | Indicates who is managing the lifetime of an object via an object -- pointer. data Managed -- | The object's lifetime is being managed manually. Unmanaged :: Managed -- | The object's lifetime is being managed by the Haskell garbage -- collector. Managed :: Managed -- | Returns the complete Haskell module name for a Module in an -- Interface, taking into account the -- interfaceHaskellModuleBase and the moduleHaskellName. getModuleName :: Interface -> Module -> String -- | Performs case conversions on the given string to ensure that it is a -- valid component of a Haskell module name. toModuleName :: String -> String -- | A partially-rendered Module. Contains all of the module's -- bindings, but may be subject to further processing. data Partial Partial :: String -> Output -> Partial -- | This is just the module name. [partialModuleHsName] :: Partial -> String [partialOutput] :: Partial -> Output -- | A chunk of generated Haskell code, including information about imports -- and exports. data Output Output :: [HsExport] -> HsImportSet -> [String] -> Set String -> Output -- | Haskell module exports. Each HsExport should include one item -- to go in the export list of the generated module. Should only contain -- objects imported or defined in the same Output. [outputExports] :: Output -> [HsExport] -- | Haskell module imports. Should include all imports needed for the -- outputBody. [outputImports] :: Output -> HsImportSet -- | Lines of Haskell code (possibly empty). These lines may not contain -- the newline character in them. There is an implicit newline between -- each string, as given by intercalate "\n" . outputBody. [outputBody] :: Output -> [String] -- | Language extensions to enable via the {--} pragma for the -- whole module. [outputExtensions] :: Output -> Set String -- | A generator monad for Haskell code. -- -- Errors thrown in this monad are of the form: -- --
--   "$problem; $context; $moreContext; $evenMoreContext."
--   
-- -- For example, "Class Foo is not convertible (use -- classModifyConversion); generating function bar; in module baz.". -- -- The main error message given to throwError should be -- capitalized and should not end with punctuation. If there is a -- suggestion, include it in parentheses at the end of the message. -- withErrorContext and inFunction add context information, -- and should be given clauses, without punctuation. type Generator = ReaderT Env (WriterT Output (Except ErrorMsg)) -- | Runs a generator action for the given interface and module name -- string. Returns an error message if an error occurred, otherwise the -- action's output together with its value. runGenerator :: Interface -> Module -> Generator a -> Either ErrorMsg (Partial, a) -- | Runs a generator action and returns the its value. evalGenerator :: Interface -> Module -> Generator a -> Either ErrorMsg a -- | Runs a generator action and returns its output. execGenerator :: Interface -> Module -> Generator a -> Either ErrorMsg Partial -- | Converts a Partial into a complete Haskell module. renderPartial :: Partial -> String -- | Returns the currently generating interface. askInterface :: Generator Interface -- | Returns the currently generating module. askModule :: Generator Module -- | Returns the currently generating module's Haskell module name. askModuleName :: Generator String -- | Looks up the Module containing a given external name, throwing -- an error if it can't be found. getModuleForExtName :: ExtName -> Generator Module -- | Adds context information to the end of any error message thrown by the -- action. See Generator. withErrorContext :: String -> Generator a -> Generator a -- | Adds the given function name to any error message thrown by the -- action, for context. inFunction :: String -> Generator a -> Generator a -- | Indicates strings that represent an item in a Haskell module export -- list. type HsExport = String -- | Adds an export to the current module. addExport :: HsExport -> Generator () -- | addExport' "x" adds an export of the form x (..) to -- the current module. addExport' :: HsExport -> Generator () -- | Adds multiple exports to the current module. addExports :: [HsExport] -> Generator () -- | Adds imports to the current module. addImports :: HsImportSet -> Generator () -- | Adds a Haskell language extension to the current module. addExtension :: String -> Generator () -- | Outputs a line of Haskell code. A newline will be added on the end of -- the input. Newline characters must not be given to this function. sayLn :: String -> Generator () -- | Outputs multiple words to form a line of Haskell code (effectively -- saysLn = sayLn . concat). saysLn :: [String] -> Generator () -- | Outputs an empty line of Haskell code. This is reportedly valid Perl -- code as well. ln :: Generator () -- | Runs the given action, indenting all code output by the action one -- level. indent :: Generator a -> Generator a -- | Runs the given action, indenting all code output by the action N -- spaces. indentSpaces :: Int -> Generator a -> Generator a -- | Takes a list of binding actions and a body action, and outputs a -- let expression. By passing in Nothing for the body, it -- will be omitted, so let statements in do blocks can -- be created as well. Output is of the form: -- --
--   let
--     <binding1>
--     ...
--     <bindingN>
--     in
--       <body>
--   
-- -- To stretch a binding over multiple lines, lines past the first should -- use indent manually. sayLet :: [Generator ()] -> Maybe (Generator ()) -> Generator () -- | Returns the Haskell name for an enum. toHsEnumTypeName :: CppEnum -> Generator String -- | Pure version of toHsEnumTypeName that doesn't create a -- qualified name. toHsEnumTypeName' :: CppEnum -> String -- | Constructs the data constructor name for a value in an enum. Like C++ -- and unlike say Java, Haskell enum values aren't in a separate -- enum-specific namespace, so we prepend the enum name to the value name -- to get the data constructor name. The value name is a list of words; -- see enumValueNames. toHsEnumCtorName :: CppEnum -> [String] -> Generator String -- | Pure version of toHsEnumCtorName that doesn't create a -- qualified name. toHsEnumCtorName' :: CppEnum -> [String] -> String -- | Returns the Haskell name for a bitspace. See toHsEnumTypeName. toHsBitspaceTypeName :: Bitspace -> Generator String -- | Pure version of toHsBitspaceTypeName that doesn't create a -- qualified name. toHsBitspaceTypeName' :: Bitspace -> String -- | Constructs the data constructor name for a value in a bitspace. See -- toHsEnumCtorName. toHsBitspaceValueName :: Bitspace -> [String] -> Generator String -- | Pure version of toHsBitspaceValueName that doesn't create a -- qualified name. toHsBitspaceValueName' :: Bitspace -> [String] -> String -- | Returns the name of the function that will convert a bitspace value -- into a raw numeric value. toHsBitspaceToNumName :: Bitspace -> Generator String -- | Pure version of toHsBitspaceToNumName that doesn't create a -- qualified name. toHsBitspaceToNumName' :: Bitspace -> String -- | The name of the Haskell typeclass that contains a method for -- converting to a bitspace value. toHsBitspaceClassName :: Bitspace -> Generator String -- | Pure version of toHsBitspaceClassName that doesn't create a -- qualified name. toHsBitspaceClassName' :: Bitspace -> String -- | The name of the method in the toHsBitspaceClassName typeclass -- that constructs bitspace values. toHsBitspaceFromValueName :: Bitspace -> Generator String -- | Pure version of toHsBitspaceFromValueName that doesn't create a -- qualified name. toHsBitspaceFromValueName' :: Bitspace -> String -- | The name for the typeclass of types that can be represented as values -- of the given C++ class. toHsValueClassName :: Class -> Generator String -- | Pure version of toHsValueClassName that doesn't create a -- qualified name. toHsValueClassName' :: Class -> String -- | The name of the method within the toHsValueClassName typeclass -- for accessing an object of the type as a pointer. toHsWithValuePtrName :: Class -> Generator String -- | Pure version of toHsWithValuePtrName that doesn't create a -- qualified name. toHsWithValuePtrName' :: Class -> String -- | The name for the typeclass of types that are (possibly const) pointers -- to objects of the given C++ class, or subclasses. toHsPtrClassName :: Constness -> Class -> Generator String -- | Pure version of toHsPtrClassName that doesn't create a -- qualified name. toHsPtrClassName' :: Constness -> Class -> String -- | The name of the function that upcasts pointers to the specific class -- type and constness. toHsCastMethodName :: Constness -> Class -> Generator String -- | Pure version of toHsCastMethodName that doesn't create a -- qualified name. toHsCastMethodName' :: Constness -> Class -> String -- | The name of the typeclass that provides a method to downcast to a -- specific class type. See toHsDownCastMethodName. toHsDownCastClassName :: Constness -> Class -> Generator String -- | Pure version of toHsDownCastClassName that doesn't create a -- qualified name. toHsDownCastClassName' :: Constness -> Class -> String -- | The name of the function that downcasts pointers to the specific class -- type and constness. toHsDownCastMethodName :: Constness -> Class -> Generator String -- | Pure version of toHsDownCastMethodName that doesn't create a -- qualified name. toHsDownCastMethodName' :: Constness -> Class -> String -- | 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 -> Class -> Generator String -- | Pure version of toHsCastPrimitiveName that doesn't create a -- qualified name. toHsCastPrimitiveName' :: Class -> Class -> String -- | 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 -> Generator String -- | Pure version of toHsConstCastFnName that doesn't create a -- qualified name. toHsConstCastFnName' :: Constness -> Class -> String -- | The name of the data type that represents a pointer to an object of -- the given class and constness. toHsDataTypeName :: Constness -> Class -> Generator String -- | Pure version of toHsDataTypeName that doesn't create a -- qualified name. toHsDataTypeName' :: Constness -> Class -> String -- | The name of a data constructor for one of the object pointer types. toHsDataCtorName :: Managed -> Constness -> Class -> Generator String -- | Pure version of toHsDataCtorName that doesn't create a -- qualified name. toHsDataCtorName' :: Managed -> Constness -> Class -> String -- | 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. toHsClassDeleteFnName' :: Class -> String -- | 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. toHsClassDeleteFnPtrName' :: Class -> String -- | Returns the name of the Haskell function that invokes the given -- constructor. toHsCtorName :: Class -> Ctor -> Generator String -- | Pure version of toHsCtorName that doesn't create a qualified -- name. toHsCtorName' :: Class -> Ctor -> String -- | Returns the name of the Haskell function that invokes the given -- method. toHsMethodName :: Class -> Method -> Generator String -- | Pure version of toHsMethodName that doesn't create a qualified -- name. toHsMethodName' :: Class -> Method -> String -- | Returns the name of the Haskell function for an entity in a class. toHsClassEntityName :: IsFnName String name => Class -> name -> Generator String -- | Pure version of toHsClassEntityName that doesn't create a -- qualified name. toHsClassEntityName' :: IsFnName String name => Class -> name -> String -- | The name of the function that takes a Haskell function and wraps it in -- a callback object. This is internal to the binding; normal users can -- pass Haskell functions to be used as callbacks inplicitly. toHsCallbackCtorName :: Callback -> Generator String -- | Pure version of toHsCallbackCtorName that doesn't create a -- qualified name. toHsCallbackCtorName' :: Callback -> String -- | The name of the function that takes a Haskell function with -- Haskell-side types and wraps it in a FunPtr that does -- appropriate conversions to and from C-side types. toHsCallbackNewFunPtrFnName :: Callback -> Generator String -- | Pure version of toHsCallbackNewFunPtrFnName that doesn't create -- a qualified name. toHsCallbackNewFunPtrFnName' :: Callback -> String -- | Converts an external name into a name suitable for a Haskell function -- or variable. toHsFnName :: ExtName -> Generator String -- | Pure version of toHsFnName that doesn't create a qualified -- name. toHsFnName' :: ExtName -> String -- | Returns a distinct argument variable name for each nonnegative number. toArgName :: Int -> String -- | The Haskell side of bindings performs conversions between C FFI types -- and Haskell types. This denotes which side's type is being used. data HsTypeSide -- | The C type sent from C++. HsCSide :: HsTypeSide -- | The Haskell-native type. HsHsSide :: HsTypeSide -- | Returns the HsType corresponding to a Type, and also -- adds imports to the Generator as necessary for Haskell types -- that the Type references. On failure, an error is thrown. cppTypeToHsTypeAndUse :: HsTypeSide -> Type -> Generator HsType -- | Returns the ClassHaskellConversion of a class. getClassHaskellConversion :: Class -> ClassHaskellConversion -- | Constructs the function type for a callback. For Haskell, the type -- depends on the side; the C++ side has additional parameters. -- -- Keep this in sync with the C++ generator's version. callbackToTFn :: HsTypeSide -> Callback -> Generator Type -- | Prints a value like prettyPrint, but removes newlines so that -- they don't cause problems with this module's textual generation. -- Should be mainly used for printing types; stripping newlines from -- definitions for example could go badly. prettyPrint :: Pretty a => a -> String instance GHC.Show.Show Foreign.Hoppy.Generator.Language.Haskell.HsTypeSide instance GHC.Classes.Eq Foreign.Hoppy.Generator.Language.Haskell.HsTypeSide instance GHC.Classes.Ord Foreign.Hoppy.Generator.Language.Haskell.Managed instance GHC.Classes.Eq Foreign.Hoppy.Generator.Language.Haskell.Managed instance GHC.Enum.Enum Foreign.Hoppy.Generator.Language.Haskell.Managed instance GHC.Enum.Bounded Foreign.Hoppy.Generator.Language.Haskell.Managed instance GHC.Classes.Eq Foreign.Hoppy.Generator.Language.Haskell.Partial instance GHC.Classes.Ord Foreign.Hoppy.Generator.Language.Haskell.Partial instance GHC.Base.Monoid Foreign.Hoppy.Generator.Language.Haskell.Output -- | 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. module Foreign.Hoppy.Generator.Spec -- | A complete specification of a C++ API. Generators for different -- languages, including the binding generator for C++, use these to -- produce their output. -- -- Interface does not have a HandlesExceptions instance -- because modifyExceptionHandlers does not work for it (handled -- exceptions cannot be modified after an Interface is -- constructed). data Interface -- | Indicates strings that are error messages. type ErrorMsg = String -- | Optional parameters when constructing an Interface with -- interface. data InterfaceOptions InterfaceOptions :: ExceptionHandlers -> InterfaceOptions [interfaceOptionsExceptionHandlers] :: InterfaceOptions -> ExceptionHandlers -- | Options used by interface. This contains no exception handlers. defaultInterfaceOptions :: InterfaceOptions -- | 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 :: String -> [Module] -> Either ErrorMsg Interface -- | Same as interface, but accepts some optional arguments. interface' :: String -> [Module] -> InterfaceOptions -> Either ErrorMsg Interface -- | The textual name of the interface. interfaceName :: Interface -> String -- | All of the individual modules, by moduleName. interfaceModules :: Interface -> Map String Module -- | Maps each ExtName exported by some module to the module that -- exports the name. interfaceNamesToModules :: Interface -> Map ExtName Module -- | 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. interfaceHaskellModuleBase :: Interface -> [String] -- | The default Haskell module under which Hoppy modules will be -- generated. This is Foreign.Hoppy.Generated, that is: -- --
--   ["Foreign", "Hoppy", "Generated"]
--   
interfaceDefaultHaskellModuleBase :: [String] -- | Sets an interface to generate all of its modules under the given -- Haskell module prefix. See interfaceHaskellModuleBase. interfaceAddHaskellModuleBase :: [String] -> Interface -> Either String Interface -- | Short qualified module import names that generated modules use to -- refer to each other tersely. interfaceHaskellModuleImportNames :: Interface -> Map Module String -- | Exceptions that all functions in the interface may throw. interfaceExceptionHandlers :: Interface -> ExceptionHandlers -- | Whether callbacks within the interface support throwing C++ exceptions -- from Haskell into C++ during their execution. This may be overridden -- by moduleCallbacksThrow and callbackThrows. interfaceCallbacksThrow :: Interface -> Bool -- | Changes callbackThrows for all callbacks in an interface that -- don't have it set explicitly at the module or callback level. interfaceSetCallbacksThrow :: Bool -> Interface -> Interface -- | 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). interfaceExceptionClassId :: Interface -> Class -> Maybe ExceptionId -- | 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. interfaceExceptionSupportModule :: Interface -> Maybe Module -- | Sets an interface's exception support module, for interfaces that use -- exceptions. interfaceSetExceptionSupportModule :: Module -> Interface -> Interface -- | 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?
--   
interfaceSetSharedPtr :: String -> Reqs -> Interface -> Interface -- | An #include directive in a C++ file. data Include -- | Creates an #include <...> directive. includeStd :: String -> Include -- | Creates an #include "..." directive. includeLocal :: String -> Include -- | Returns the complete #include ... line for an include, -- including trailing newline. includeToString :: Include -> String -- | 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. data Module -- | The module's name. A module name must identify a unique module within -- an Interface. moduleName :: Module -> String -- | A relative path under a C++ sources root to which the generator will -- write a header file for the module's C++ bindings. moduleHppPath :: Module -> String -- | A relative path under a C++ sources root to which the generator will -- write a source file for the module's C++ bindings. moduleCppPath :: Module -> String -- | All of the exports in a module. moduleExports :: Module -> Map ExtName Export -- | Module-level requirements. moduleReqs :: Module -> Reqs -- | Exceptions that all functions in the module may throw. moduleExceptionHandlers :: Module -> ExceptionHandlers -- | Whether callbacks exported from the module support exceptions being -- thrown during their execution. When present, this overrides -- interfaceCallbacksThrow. This maybe overridden by -- callbackThrows. moduleCallbacksThrow :: Module -> Maybe Bool -- | Changes callbackThrows for all callbacks in a module that don't -- have it set explicitly. moduleSetCallbacksThrow :: MonadState Module m => Maybe Bool -> m () -- | The module's addendum. moduleAddendum :: Module -> Addendum -- | The generated Haskell module name, underneath the -- interfaceHaskellModuleBase. If absent (by default), the -- moduleName is used. May be modified with -- moduleAddHaskellName. moduleHaskellName :: Module -> Maybe [String] -- | Creates an empty module, ready to be configured with -- moduleModify. makeModule :: String -> String -> String -> Module -- | Extends a module. To be used with the module state-monad actions in -- this package. moduleModify :: Module -> StateT Module (Either String) () -> Either ErrorMsg Module -- | 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. moduleModify' :: Module -> StateT Module (Either String) () -> Module -- | Replaces a module's moduleHppPath. moduleSetHppPath :: MonadState Module m => String -> m () -- | Replaces a module's moduleCppPath. moduleSetCppPath :: MonadState Module m => String -> m () -- | 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. moduleAddExports :: (MonadError String m, MonadState Module m) => [Export] -> m () -- | Changes a module's moduleHaskellName from the default. This can -- only be called once on a module. moduleAddHaskellName :: (MonadError String m, MonadState Module m) => [String] -> m () -- | 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. data Reqs -- | The includes specified by a Reqs. reqsIncludes :: Reqs -> Set Include -- | Creates a Reqs that contains the given include. reqInclude :: Include -> Reqs -- | 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. class HasReqs a -- | Returns an object's requirements. getReqs :: HasReqs a => a -> Reqs -- | Replaces an object's requirements with new ones. setReqs :: HasReqs a => Reqs -> a -> a -- | Modifies an object's requirements. modifyReqs :: HasReqs a => (Reqs -> Reqs) -> a -> a -- | Adds to a object's requirements. addReqs :: HasReqs a => Reqs -> a -> a -- | Adds a list of includes to the requirements of an object. addReqIncludes :: HasReqs a => [Include] -> a -> a -- | 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. data ExtName -- | Creates an ExtName that contains the given string, erroring if -- the string is an invalid ExtName. toExtName :: String -> ExtName -- | Returns true if the given string is represents a valid ExtName. isValidExtName :: String -> Bool -- | Returns the string an an ExtName contains. fromExtName :: ExtName -> String -- | Types that have an external name, and also optionally have nested -- entities with external names as well. See getAllExtNames. class HasExtNames a -- | Returns the external name by which a given entity is referenced. getPrimaryExtName :: HasExtNames a => a -> ExtName -- | Returns external names nested within the given entity. Does not -- include the primary external name. getNestedExtNames :: HasExtNames a => a -> [ExtName] -- | Returns a list of all of the external names an entity contains. This -- combines both getPrimaryExtName and getNestedExtNames. getAllExtNames :: HasExtNames a => a -> [ExtName] -- | The C++ name of a function or method. data FnName name -- | A regular, "alphanumeric" name. The exact type depends on what kind of -- object is being named. FnName :: name -> FnName name -- | An operator name. FnOp :: Operator -> FnName name -- | Enables implementing automatic conversions to a FnName -- t. class IsFnName t a toFnName :: IsFnName t a => a -> FnName t -- | Overloadable C++ operators. data Operator -- |
--   x(...)
--   
OpCall :: Operator -- |
--   x, y
--   
OpComma :: Operator -- |
--   x = y
--   
OpAssign :: Operator -- |
--   x[y]
--   
OpArray :: Operator -- |
--   *x
--   
OpDeref :: Operator -- |
--   &x
--   
OpAddress :: Operator -- |
--   x + y
--   
OpAdd :: Operator -- |
--   x += y
--   
OpAddAssign :: Operator -- |
--   x - y
--   
OpSubtract :: Operator -- |
--   x -= y
--   
OpSubtractAssign :: Operator -- |
--   x * y
--   
OpMultiply :: Operator -- |
--   x *= y
--   
OpMultiplyAssign :: Operator -- |
--   x / y
--   
OpDivide :: Operator -- |
--   x /= y
--   
OpDivideAssign :: Operator -- |
--   x % y
--   
OpModulo :: Operator -- |
--   x %= y
--   
OpModuloAssign :: Operator -- |
--   +x
--   
OpPlus :: Operator -- |
--   -x
--   
OpMinus :: Operator -- |
--   ++x
--   
OpIncPre :: Operator -- |
--   x++
--   
OpIncPost :: Operator -- |
--   --x
--   
OpDecPre :: Operator -- |
--   x--
--   
OpDecPost :: Operator -- |
--   x == y
--   
OpEq :: Operator -- |
--   x != y
--   
OpNe :: Operator -- |
--   x < y
--   
OpLt :: Operator -- |
--   x <= y
--   
OpLe :: Operator -- |
--   x > y
--   
OpGt :: Operator -- |
--   x >= y
--   
OpGe :: Operator -- |
--   !x
--   
OpNot :: Operator -- |
--   x && y
--   
OpAnd :: Operator -- |
--   x || y
--   
OpOr :: Operator -- |
--   ~x
--   
OpBitNot :: Operator -- |
--   x & y
--   
OpBitAnd :: Operator -- |
--   x &= y
--   
OpBitAndAssign :: Operator -- |
--   x | y
--   
OpBitOr :: Operator -- |
--   x |= y
--   
OpBitOrAssign :: Operator -- |
--   x ^ y
--   
OpBitXor :: Operator -- |
--   x ^= y
--   
OpBitXorAssign :: Operator -- |
--   x << y
--   
OpShl :: Operator -- |
--   x <<= y
--   
OpShlAssign :: Operator -- |
--   x >> y
--   
OpShr :: Operator -- |
--   x >>= y
--   
OpShrAssign :: Operator -- | The arity and syntax of an operator. data OperatorType -- | Prefix unary operators. Examples: !x, *x, -- ++x. UnaryPrefixOperator :: String -> OperatorType -- | Postfix unary operators. Examples: x--, x++. UnaryPostfixOperator :: String -> OperatorType -- | Infix binary operators. Examples: x * y, x >>= -- y. BinaryOperator :: String -> OperatorType -- | x(...) with arbitrary arity. CallOperator :: OperatorType -- | x[y], a binary operator with non-infix syntax. ArrayOperator :: OperatorType -- | Returns a conventional string to use for the ExtName of an -- operator. operatorPreferredExtName :: Operator -> ExtName -- | Returns a conventional name for an operator, as with -- operatorPreferredExtName, but as a string. operatorPreferredExtName' :: Operator -> String -- | Returns the type of an operator. operatorType :: Operator -> OperatorType -- | Specifies some C++ object (function or class) to give access to. data Export -- | Exports a variable. ExportVariable :: Variable -> Export -- | Exports an enum. ExportEnum :: CppEnum -> Export -- | Exports a bitspace. ExportBitspace :: Bitspace -> Export -- | Exports a function. ExportFn :: Function -> Export -- | Exports a class with all of its contents. ExportClass :: Class -> Export -- | Exports a callback. ExportCallback :: Callback -> Export -- | Returns the export's addendum. Export doesn't have a -- HasAddendum instance because you normally wouldn't want to -- modify the addendum of one. exportAddendum :: Export -> Addendum -- | 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). data Identifier -- | The separate parts of the identifier, between ::s. identifierParts :: Identifier -> [IdPart] -- | A single component of an Identifier, between ::s. data IdPart -- | The name within the enclosing scope. idPartBase :: IdPart -> String -- | Template arguments, if present. idPartArgs :: IdPart -> Maybe [Type] -- | Creates an identifier of the form a. ident :: String -> Identifier -- | Creates an identifier of the form a1::a2::...::aN. ident' :: [String] -> Identifier -- | Creates an identifier of the form a::b. ident1 :: String -> String -> Identifier -- | Creates an identifier of the form a::b::c. ident2 :: String -> String -> String -> Identifier -- | Creates an identifier of the form a::b::c::d. ident3 :: String -> String -> String -> String -> Identifier -- | Creates an identifier of the form a::b::c::d::e. ident4 :: String -> String -> String -> String -> String -> Identifier -- | Creates an identifier of the form a::b::c::d::e::f. ident5 :: String -> String -> String -> String -> String -> String -> Identifier -- | Creates an identifier of the form a<...>. identT :: String -> [Type] -> Identifier -- | Creates an identifier with arbitrary many templated and non-templated -- parts. identT' :: [(String, Maybe [Type])] -> Identifier -- | Creates an identifier of the form a::b<...>. ident1T :: String -> String -> [Type] -> Identifier -- | Creates an identifier of the form a::b::c<...>. ident2T :: String -> String -> String -> [Type] -> Identifier -- | Creates an identifier of the form a::b::c::d<...>. ident3T :: String -> String -> String -> String -> [Type] -> Identifier -- | Creates an identifier of the form a::b::c::d::e<...>. ident4T :: String -> String -> String -> String -> String -> [Type] -> Identifier -- | Creates an identifier of the form -- a::b::c::d::e::f<...>. ident5T :: String -> String -> String -> String -> String -> String -> [Type] -> Identifier -- | 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. data Type Internal_TVoid :: Type Internal_TBool :: Type Internal_TChar :: Type Internal_TUChar :: Type Internal_TShort :: Type Internal_TUShort :: Type Internal_TInt :: Type Internal_TUInt :: Type Internal_TLong :: Type Internal_TULong :: Type Internal_TLLong :: Type Internal_TULLong :: Type Internal_TFloat :: Type Internal_TDouble :: Type Internal_TInt8 :: Type Internal_TInt16 :: Type Internal_TInt32 :: Type Internal_TInt64 :: Type Internal_TWord8 :: Type Internal_TWord16 :: Type Internal_TWord32 :: Type Internal_TWord64 :: Type Internal_TPtrdiff :: Type Internal_TSize :: Type Internal_TSSize :: Type Internal_TEnum :: CppEnum -> Type Internal_TBitspace :: Bitspace -> Type Internal_TPtr :: Type -> Type Internal_TRef :: Type -> Type Internal_TFn :: [Type] -> Type -> Type Internal_TCallback :: Callback -> Type Internal_TObj :: Class -> Type Internal_TObjToHeap :: Class -> Type Internal_TToGc :: Type -> Type Internal_TConst :: Type -> Type -- | Canonicalizes a Type without changing its meaning. Multiple -- nested Internal_TConsts are collapsed into a single one. normalizeType :: Type -> Type -- | Strips leading Internal_TConsts off of a type. stripConst :: Type -> Type -- | A C++ variable. -- -- Use this data type's HasReqs instance to make the variable -- accessible. data Variable -- | Creates a binding for a C++ variable. makeVariable :: Identifier -> Maybe ExtName -> Type -> Variable -- | The identifier used to refer to the variable. varIdentifier :: Variable -> Identifier -- | The variable's external name. varExtName :: Variable -> ExtName -- | The variable's type. This may be constT to indicate that the -- variable is read-only. varType :: Variable -> Type -- | Requirements for bindings to access this variable. varReqs :: Variable -> Reqs -- | Returns whether the variable is constant, i.e. whether its type is -- constT .... varIsConst :: Variable -> Bool -- | Returns the external name of the getter function for the variable. varGetterExtName :: Variable -> ExtName -- | Returns the external name of the setter function for the variable. varSetterExtName :: Variable -> ExtName -- | 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. data CppEnum -- | Creates a binding for a C++ enum. makeEnum :: Identifier -> Maybe ExtName -> [(Int, [String])] -> CppEnum -- | The identifier used to refer to the enum. enumIdentifier :: CppEnum -> Identifier -- | The enum's external name. enumExtName :: CppEnum -> ExtName -- | 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. enumValueNames :: CppEnum -> [(Int, [String])] -- | Requirements for bindings to access this enum. Currently unused, but -- will be in the future. enumReqs :: CppEnum -> Reqs -- | The prefix applied to value names (enumValueNames) when -- determining the names of values in foreign languages. This defaults to -- the external name of the enum, plus an underscore. -- -- See enumSetValuePrefix. enumValuePrefix :: CppEnum -> String -- | Sets the prefix applied to the names of enum values' identifiers in -- foreign languages. -- -- See enumValuePrefix. enumSetValuePrefix :: String -> CppEnum -> CppEnum -- | 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. data Bitspace -- | Creates a binding for a C++ bitspace. makeBitspace :: ExtName -> Type -> [(Int, [String])] -> Bitspace -- | The bitspace's external name. bitspaceExtName :: Bitspace -> ExtName -- | The C++ type used for bits values. This should be a primitive numeric -- type, usually intT. bitspaceType :: Bitspace -> Type -- | The numeric values and names of the bitspace values. See -- enumValueNames. bitspaceValueNames :: Bitspace -> [(Int, [String])] -- | An associated enum, whose values may be converted to values in the -- bitspace. bitspaceEnum :: Bitspace -> Maybe CppEnum -- | Associates an enum with the bitspace. See bitspaceEnum. bitspaceAddEnum :: CppEnum -> Bitspace -> Bitspace -- | The optional C++ type for a bitspace. bitspaceCppTypeIdentifier :: Bitspace -> Maybe Identifier -- | The name of a C++ function to convert from the bitspace's C++ type to -- bitspaceType. bitspaceFromCppValueFn :: Bitspace -> Maybe String -- | The name of a C++ function to convert from bitspaceType to the -- bitspace's C++ type. bitspaceToCppValueFn :: Bitspace -> Maybe String -- | 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. bitspaceAddCppType :: Identifier -> Maybe String -> Maybe String -> Bitspace -> Bitspace -- | 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. bitspaceReqs :: Bitspace -> Reqs -- | The prefix applied to value names (bitspaceValueNames) when -- determining the names of values in foreign languages. This defaults to -- the external name of the bitspace, plus an underscore. -- -- See bitspaceSetValuePrefix. bitspaceValuePrefix :: Bitspace -> String -- | Sets the prefix applied to the names of enum values' identifiers in -- foreign languages. -- -- See enumValuePrefix. bitspaceSetValuePrefix :: String -> Bitspace -> Bitspace -- | 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. data Purity -- | Side-affects are possible. Nonpure :: Purity -- | Side-affects will not happen. Pure :: Purity -- | A C++ function declaration. -- -- Use this data type's HasReqs instance to make the function -- accessible. You do not need to add requirements for parameter or -- return types. data Function -- | Creates a binding for a C++ function. makeFn :: IsFnName Identifier name => name -> Maybe ExtName -> Purity -> [Type] -> Type -> Function -- | The identifier used to call the function. fnCName :: Function -> FnName Identifier -- | The function's external name. fnExtName :: Function -> ExtName -- | Whether the function is pure. fnPurity :: Function -> Purity -- | The function's parameter types. fnParams :: Function -> [Type] -- | The function's return type. fnReturn :: Function -> Type -- | Requirements for bindings to access this function. fnReqs :: Function -> Reqs -- | Exceptions that the function might throw. fnExceptionHandlers :: Function -> ExceptionHandlers -- | 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. data Class -- | Creates a binding for a C++ class and its contents. makeClass :: Identifier -> Maybe ExtName -> [Class] -> [ClassEntity] -> Class -- | The identifier used to refer to the class. classIdentifier :: Class -> Identifier -- | The class's external name. classExtName :: Class -> ExtName -- | The class's public superclasses. classSuperclasses :: Class -> [Class] -- | The class's entities. classEntities :: Class -> [ClassEntity] -- | Adds constructors to a class. classAddEntities :: [ClassEntity] -> Class -> Class -- | Returns all of the class's variables. classVariables :: Class -> [ClassVariable] -- | Returns all of the class's constructors. classCtors :: Class -> [Ctor] -- | Returns all of the class's methods, including methods generated from -- Props. classMethods :: Class -> [Method] -- | The class's methods. classDtorIsPublic :: Class -> Bool -- | Marks a class's destructor as private, so that a binding for it won't -- be generated. classSetDtorPrivate :: Class -> Class -- | Behaviour for converting objects to and from foriegn values. classConversion :: Class -> ClassConversion -- | Requirements for bindings to access this class. classReqs :: Class -> Reqs -- | 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. classEntityPrefix :: Class -> String -- | Sets the prefix applied to foreign languages' entities generated from -- methods, etc. within the class. -- -- See IsClassEntity and classEntityPrefix. classSetEntityPrefix :: String -> Class -> Class -- | This is true for classes passed through -- classSetMonomorphicSuperclass. classIsMonomorphicSuperclass :: Class -> Bool -- | 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. classSetMonomorphicSuperclass :: Class -> Class -- | This is true for classes passed through -- classSetSubclassOfMonomorphic. classIsSubclassOfMonomorphic :: Class -> Bool -- | 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. classSetSubclassOfMonomorphic :: Class -> Class -- | Whether to support using the class as a C++ exception. classIsException :: Class -> Bool -- | Marks a class as being used as an exception. This makes the class -- throwable and catchable. classMakeException :: Class -> Class -- | A C++ entity that belongs to a class. data ClassEntity CEVar :: ClassVariable -> ClassEntity CECtor :: Ctor -> ClassEntity CEMethod :: Method -> ClassEntity CEProp :: Prop -> ClassEntity -- | 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. class IsClassEntity a -- | Extracts the external name of the object, without the class name -- added. classEntityExtNameSuffix :: IsClassEntity a => a -> ExtName -- | 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. classEntityExtName :: IsClassEntity a => Class -> a -> ExtName -- | 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 :: IsClassEntity a => Class -> a -> ExtName -- | 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. classEntityForeignName' :: Class -> ExtName -> ExtName -- | A C++ member variable. data ClassVariable -- | Creates a ClassVariable with full generality and manual name -- specification. -- -- The result is wrapped in a CEVar. For an unwrapped value, use -- makeClassVariable_. makeClassVariable :: String -> Maybe ExtName -> Type -> Staticness -> Bool -> ClassEntity -- | The unwrapped version of makeClassVariable. makeClassVariable_ :: String -> Maybe ExtName -> Type -> Staticness -> Bool -> ClassVariable -- | Creates a ClassVariable for a nonstatic class variable for -- class::varName whose external name is class_varName. -- -- The result is wrapped in a CEVar. For an unwrapped value, use -- mkClassVariable_. mkClassVariable :: String -> Type -> ClassEntity -- | The unwrapped version of mkClassVariable. mkClassVariable_ :: String -> Type -> ClassVariable -- | Same as mkClassVariable, but returns a static variable instead. -- -- The result is wrapped in a CEVar. For an unwrapped value, use -- mkStaticClassVariable_. mkStaticClassVariable :: String -> Type -> ClassEntity -- | The unwrapped version of mkStaticClassVariable. mkStaticClassVariable_ :: String -> Type -> ClassVariable -- | The variable's C++ name. classVarCName :: ClassVariable -> String -- | The variable's external name. classVarExtName :: ClassVariable -> ExtName -- | The variable's type. This may be constT to indicate that the -- variable is read-only. classVarType :: ClassVariable -> Type -- | Whether the variable is static (i.e. whether it exists once in the -- class itself and not in each instance). classVarStatic :: ClassVariable -> Staticness -- | Whether the variable should have an accompanying getter. Note this -- exists only for disabling getters on callback variables - as there is -- currently no functionality to pass callbacks out of c++ classVarGettable :: ClassVariable -> Bool -- | Returns the external name of the getter function for the class -- variable. classVarGetterExtName :: Class -> ClassVariable -> ExtName -- | Returns the foreign name of the getter function for the class -- variable. classVarGetterForeignName :: Class -> ClassVariable -> ExtName -- | Returns the external name of the setter function for the class -- variable. classVarSetterExtName :: Class -> ClassVariable -> ExtName -- | Returns the foreign name of the setter function for the class -- variable. classVarSetterForeignName :: Class -> ClassVariable -> ExtName -- | A C++ class constructor declaration. data Ctor -- | Creates a Ctor with full generality. -- -- The result is wrapped in a CECtor. For an unwrapped value, use -- makeCtor_. makeCtor :: ExtName -> [Type] -> ClassEntity -- | The unwrapped version of makeCtor. makeCtor_ :: ExtName -> [Type] -> Ctor -- | 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 :: String -> [Type] -> ClassEntity -- | The unwrapped version of mkCtor. mkCtor_ :: String -> [Type] -> Ctor -- | The constructor's external name. ctorExtName :: Ctor -> ExtName -- | The constructor's parameter types. ctorParams :: Ctor -> [Type] -- | Exceptions that the constructor may throw. ctorExceptionHandlers :: Ctor -> ExceptionHandlers -- | 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 Method -- | The C++ code to which a Method is bound. data MethodImpl -- | The Method is bound to an actual class method. RealMethod :: (FnName String) -> MethodImpl -- | 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. FnMethod :: (FnName Identifier) -> MethodImpl -- | How a method is associated to its class. A method may be static, -- const, or neither (a regular method). data MethodApplicability MNormal :: MethodApplicability MStatic :: MethodApplicability MConst :: MethodApplicability -- | Whether or not a method is const. data Constness Nonconst :: Constness Const :: Constness -- | Returns the opposite constness value. constNegate :: Constness -> Constness -- | Whether or not a method is static. data Staticness Nonstatic :: Staticness Static :: Staticness -- | Creates a Method with full generality and manual name -- specification. -- -- The result is wrapped in a CEMethod. For an unwrapped value, -- use makeMethod_. makeMethod :: IsFnName String name => name -> ExtName -> MethodApplicability -> Purity -> [Type] -> Type -> ClassEntity -- | The unwrapped version of makeMethod. makeMethod_ :: IsFnName String name => name -> ExtName -> MethodApplicability -> Purity -> [Type] -> Type -> Method -- | Creates a Method that is in fact backed by a C++ non-member -- function (a la makeFn), but appears to be a regular method. -- This is useful for wrapping a method on the C++ side when its -- arguments aren't right for binding directly. -- -- A this pointer parameter is not automatically added to -- the parameter list for non-static methods created with -- makeFnMethod. -- -- The result is wrapped in a CEMethod. For an unwrapped value, -- use makeFnMethod_. makeFnMethod :: IsFnName Identifier name => name -> String -> MethodApplicability -> Purity -> [Type] -> Type -> ClassEntity -- | The unwrapped version of makeFnMethod. makeFnMethod_ :: IsFnName Identifier name => name -> String -> MethodApplicability -> Purity -> [Type] -> 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'. -- -- The result is wrapped in a CEMethod. For an unwrapped value, -- use mkMethod_. mkMethod :: IsFnName String name => name -> [Type] -> Type -> ClassEntity -- | The unwrapped version of mkMethod. mkMethod_ :: IsFnName String name => name -> [Type] -> 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. -- -- The result is wrapped in a CEMethod. For an unwrapped value, -- use mkMethod'_. mkMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> ClassEntity -- | The unwrapped version of mkMethod'. mkMethod'_ :: IsFnName String name => name -> String -> [Type] -> Type -> Method -- | Same as mkMethod, but returns an MConst method. -- -- The result is wrapped in a CEMethod. For an unwrapped value, -- use mkConstMethod_. mkConstMethod :: IsFnName String name => name -> [Type] -> Type -> ClassEntity -- | The unwrapped version of mkConstMethod. mkConstMethod_ :: IsFnName String name => name -> [Type] -> Type -> Method -- | Same as mkMethod', but returns an MConst method. -- -- The result is wrapped in a CEMethod. For an unwrapped value, -- use mkConstMethod'_. mkConstMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> ClassEntity -- | The unwrapped version of mkConstMethod'. mkConstMethod'_ :: IsFnName String name => name -> String -> [Type] -> Type -> Method -- | Same as mkMethod, but returns an MStatic method. -- -- The result is wrapped in a CEMethod. For an unwrapped value, -- use mkStaticMethod_. mkStaticMethod :: IsFnName String name => name -> [Type] -> Type -> ClassEntity -- | The unwrapped version of mkStaticMethod. mkStaticMethod_ :: IsFnName String name => name -> [Type] -> Type -> Method -- | Same as mkMethod', but returns an MStatic method. -- -- The result is wrapped in a CEMethod. For an unwrapped value, -- use mkStaticMethod'_. mkStaticMethod' :: IsFnName String name => name -> String -> [Type] -> Type -> ClassEntity -- | The unwrapped version of mkStaticMethod'. mkStaticMethod'_ :: IsFnName String name => name -> String -> [Type] -> Type -> Method -- | A "property" getter/setter pair. data Prop -- | 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 -> ClassEntity -- | The unwrapped version of mkProp. mkProp_ :: String -> Type -> Prop -- | Creates a getter/setter binding pair for static methods: -- --
--   static T foo() const
--   static void setFoo(T)
--   
mkStaticProp :: String -> Type -> ClassEntity -- | The unwrapped version of mkStaticProp. mkStaticProp_ :: String -> Type -> Prop -- | 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 -> ClassEntity -- | The unwrapped version of mkBoolIsProp. mkBoolIsProp_ :: String -> Prop -- | 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 -> ClassEntity -- | The unwrapped version of mkBoolHasProp. mkBoolHasProp_ :: String -> Prop -- | The underlying code that the binding calls. methodImpl :: Method -> MethodImpl -- | The method's external name. methodExtName :: Method -> ExtName -- | How the method is associated to its class. methodApplicability :: Method -> MethodApplicability -- | Whether the method is pure. methodPurity :: Method -> Purity -- | The method's parameter types. methodParams :: Method -> [Type] -- | The method's return type. methodReturn :: Method -> Type -- | Exceptions that the method might throw. methodExceptionHandlers :: Method -> ExceptionHandlers -- | Returns the constness of a method, based on its -- methodApplicability. methodConst :: Method -> Constness -- | Returns the staticness of a method, based on its -- methodApplicability. methodStatic :: Method -> Staticness -- | 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. data ClassConversion ClassConversion :: ClassHaskellConversion -> ClassConversion -- | Conversions to and from Haskell. [classHaskellConversion] :: ClassConversion -> ClassHaskellConversion -- | Conversion behaviour for a class that is not convertible. classConversionNone :: ClassConversion -- | Modifies a class's ClassConversion structure with a given -- function. classModifyConversion :: (ClassConversion -> ClassConversion) -> Class -> Class -- | Replaces a class's ClassConversion structure. classSetConversion :: ClassConversion -> Class -> Class -- | Controls how conversions between C++ objects and Haskell values happen -- in Haskell bindings. data ClassHaskellConversion ClassHaskellConversion :: Maybe (Generator HsType) -> Maybe (Generator ()) -> Maybe (Generator ()) -> ClassHaskellConversion -- | 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. [classHaskellConversionType] :: ClassHaskellConversion -> Maybe (Generator HsType) -- | Produces a Haskell expression that evaluates to a function that takes -- an value of the type that classHaskellConversionType generates, -- and returns a non-const handle for a new C++ object in IO. The -- generator must output code and may add imports, but must not add -- exports. -- -- If this field is present, then classHaskellConversionType must -- also be present. [classHaskellConversionToCppFn] :: ClassHaskellConversion -> Maybe (Generator ()) -- | Produces a Haskell expression that evaluates to a function that takes -- a const handle for a C++ object, and returns a value of the type that -- classHaskellConversionType generates, in IO. It should not -- delete the handle. The generator must output code and may add imports, -- but must not add exports. -- -- If this field is present, then classHaskellConversionType must -- also be present. [classHaskellConversionFromCppFn] :: ClassHaskellConversion -> Maybe (Generator ()) -- | Conversion behaviour for a class that is not convertible to or from -- Haskell. classHaskellConversionNone :: ClassHaskellConversion -- | Replaces a class's classHaskellConversion with a given value. classSetHaskellConversion :: ClassHaskellConversion -> Class -> Class -- | A non-C++ function that can be invoked via a C++ functor or function -- pointer. -- -- Use this data type's HasReqs instance to add extra -- requirements, however manually adding requirements for parameter and -- return types is not necessary. data Callback -- | Creates a binding for constructing callbacks into foreign code. makeCallback :: ExtName -> [Type] -> Type -> Callback -- | The callback's external name. callbackExtName :: Callback -> ExtName -- | The callback's parameter types. callbackParams :: Callback -> [Type] -- | The callback's return type. callbackReturn :: Callback -> Type -- | Whether the callback supports throwing C++ exceptions from Haskell -- into C++ during its execution. When absent, the value is inherited -- from moduleCallbacksThrow and interfaceCallbacksThrow. callbackThrows :: Callback -> Maybe Bool -- | Extra requirements for the callback. callbackReqs :: Callback -> Reqs -- | Sets whether a callback supports handling thrown C++ exceptions and -- passing them into C++. callbackSetThrows :: Bool -> Callback -> Callback -- | Each exception class has a unique exception ID. newtype ExceptionId ExceptionId :: Int -> ExceptionId -- | Internal. [getExceptionId] :: ExceptionId -> Int -- | The exception ID that represents the catch-all type. exceptionCatchAllId :: ExceptionId -- | Indicates the ability to handle a certain type of C++ exception. data ExceptionHandler -- | Indicates that instances of the given class are handled (including -- derived types). CatchClass :: Class -> ExceptionHandler -- | Indicates that all C++ exceptions are handled, i.e. catch -- (...). CatchAll :: ExceptionHandler -- | 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. data ExceptionHandlers ExceptionHandlers :: [ExceptionHandler] -> ExceptionHandlers -- | Extracts the list of exception handlers. [exceptionHandlersList] :: ExceptionHandlers -> [ExceptionHandler] -- | Types that can handle exceptions. class HandlesExceptions a -- | Extracts the exception handlers for an object. getExceptionHandlers :: HandlesExceptions a => a -> ExceptionHandlers -- | Appends additional exception handlers to an object. handleExceptions :: HandlesExceptions a => [ExceptionHandler] -> a -> a -- | 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). data Addendum Addendum :: Generator () -> Addendum -- | Code to be output into the Haskell binding. May also add imports and -- exports. [addendumHaskell] :: Addendum -> Generator () -- | A typeclass for types that have an addendum. class HasAddendum a -- | Returns an object's addendum. getAddendum :: HasAddendum a => a -> Addendum -- | Replaces and object's addendum with another. setAddendum :: HasAddendum a => Addendum -> a -> a -- | Modified an object's addendum. modifyAddendum :: HasAddendum a => (Addendum -> Addendum) -> a -> a -- | Adds a Haskell addendum to an object. addAddendumHaskell :: HasAddendum a => Generator () -> a -> a -- | A Haskell module name. type HsModuleName = String -- | 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 HsImportSet -- | References an occurrence of an import statement, under which bindings -- can be imported. Only imported specs under equal HsImportKeys -- may be merged. data HsImportKey HsImportKey :: HsModuleName -> Maybe HsModuleName -> HsImportKey [hsImportModule] :: HsImportKey -> HsModuleName [hsImportQualifiedName] :: HsImportKey -> Maybe HsModuleName -- | 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. data HsImportSpecs HsImportSpecs :: Maybe (Map HsImportName HsImportVal) -> Bool -> HsImportSpecs [getHsImportSpecs] :: HsImportSpecs -> Maybe (Map HsImportName HsImportVal) [hsImportSource] :: HsImportSpecs -> Bool -- | An identifier that can be imported from a module. Symbols may be used -- here when surrounded by parentheses. Examples are "fmap" and -- "(++)". type HsImportName = String -- | Specifies how a name is imported. data HsImportVal -- | The name is imported, and nothing underneath it is. HsImportVal :: HsImportVal -- | The name is imported, as are specific names underneath it. This is a -- X (a, b, c) import. HsImportValSome :: [HsImportName] -> HsImportVal -- | The name is imported, along with all names underneath it. This is a -- X (..) import. HsImportValAll :: HsImportVal -- | An import for the entire contents of a Haskell module. hsWholeModuleImport :: HsModuleName -> HsImportSet -- | A qualified import of a Haskell module. hsQualifiedImport :: HsModuleName -> HsModuleName -> HsImportSet -- | An import of a single name from a Haskell module. hsImport1 :: HsModuleName -> HsImportName -> HsImportSet -- | A detailed import of a single name from a Haskell module. hsImport1' :: HsModuleName -> HsImportName -> HsImportVal -> HsImportSet -- | An import of multiple names from a Haskell module. hsImports :: HsModuleName -> [HsImportName] -> HsImportSet -- | A detailed import of multiple names from a Haskell module. hsImports' :: HsModuleName -> [(HsImportName, HsImportVal)] -> HsImportSet -- | Sets all of the import specifications in an import set to be -- {--} imports. hsImportSetMakeSource :: HsImportSet -> HsImportSet -- | Returns all of the exception classes in an interface. interfaceAllExceptionClasses :: Interface -> [Class] -- | 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. interfaceSharedPtr :: Interface -> (Reqs, String) -- | Searches a class for a copy constructor, returning it if found. classFindCopyCtor :: Class -> Maybe Ctor -- | Constructor for an import set. makeHsImportSet :: Map HsImportKey HsImportSpecs -> HsImportSet -- | Returns the import set's internal map from module names to imported -- bindings. getHsImportSet :: HsImportSet -> Map HsImportKey HsImportSpecs -- | Imports Data.Bits qualified as HoppyDB. hsImportForBits :: HsImportSet -- | Imports Control.Exception qualified as HoppyCE. hsImportForException :: HsImportSet -- | Imports Data.Int qualified as HoppyDI. hsImportForInt :: HsImportSet -- | Imports Data.Word qualified as HoppyDW. hsImportForWord :: HsImportSet -- | Imports Foreign qualified as HoppyF. hsImportForForeign :: HsImportSet -- | Imports Foreign.C qualified as HoppyFC. hsImportForForeignC :: HsImportSet -- | Imports Data.Map qualified as HoppyDM. hsImportForMap :: HsImportSet -- | Imports Prelude qualified as HoppyP. hsImportForPrelude :: HsImportSet -- | Imports Foreign.Hoppy.Runtime qualified as HoppyFHR. hsImportForRuntime :: HsImportSet -- | Imports System.Posix.Types qualified as HoppySPT. hsImportForSystemPosixTypes :: HsImportSet -- | Imports Data.Typeable qualified as HoppyDT. hsImportForTypeable :: HsImportSet -- | Imports System.IO.Unsafe qualified as HoppySIU. hsImportForUnsafeIO :: HsImportSet -- | Returns an error message indicating that objToHeapT is used -- where data is going from a foreign language into C++. objToHeapTWrongDirectionErrorMsg :: Maybe String -> Class -> String -- | Returns an error message indicating that objToHeapT is used -- where data is going from a foreign language into C++. tToGcInvalidFormErrorMessage :: Maybe String -> Type -> String -- | Returns an error message indicating that toGcT is used where -- data is going from a foreign language into C++. toGcTWrongDirectionErrorMsg :: Maybe String -> Type -> String -- | Modifies a class's ClassConversion structure by setting all -- languages to use ClassConversionToHeap. classSetConversionToHeap :: Class -> Class -- | Modifies a class's ClassConversion structure by setting all -- languages that support garbage collection to use -- ClassConversionToGc. classSetConversionToGc :: Class -> Class -- | Shared portion of the C++ code generator. Usable by binding -- definitions. module Foreign.Hoppy.Generator.Language.Cpp -- | Returns the C++ binding function name for an external name. externalNameToCpp :: ExtName -> String -- | Returns the C++ binding function name of the wrapper for the delete -- method for a class. classDeleteFnCppName :: Class -> String -- | classCastFnCppName fromCls toCls returns the name of the -- generated C++ function that casts a pointer from fromCls to -- toCls. classCastFnCppName :: Class -> Class -> String -- | Returns the name of the outer, copyable class for a callback. callbackClassName :: Callback -> String -- | Returns the name of the internal, non-copyable implementation class -- for a callback. callbackImplClassName :: Callback -> String -- | Returns the name of the C++ binding function that creates a C++ -- callback wrapper object from a function pointer to foreign code. callbackFnName :: Callback -> String -- | Returns a distinct argument variable name for each nonnegative number. toArgName :: Int -> String -- | Same as toArgName, but with distinct names, with with -- similarity between toArgName n and toArgNameAlt n. toArgNameAlt :: Int -> String -- | The C++ variable name to use for the exception ID argument in a -- gateway function. exceptionIdArgName :: String -- | The C++ variable name to use for the exception pointer argument in a -- gateway function. exceptionPtrArgName :: String -- | The C++ variable name to use in a catch statement in a -- gateway function. exceptionVarName :: String -- | The name of the C++ function that receives an exception from a foreign -- language and throws it in C++. exceptionRethrowFnName :: String -- | A chunk is a string that contains an arbitrary portion of C++ code. -- The only requirement is that chunk boundaries are also C++ token -- boundaries, because the generator monad automates the process of -- inserting whitespace between chunk boundaries where necessary. newtype Chunk Chunk :: String -> Chunk [chunkContents] :: Chunk -> String -- | Runs a Chunk writer, combining them with combineChunks -- to form a single string. runChunkWriter :: Writer [Chunk] a -> (a, String) -- | Runs a Chunk writer and returns the monad's value. evalChunkWriter :: Writer [Chunk] a -> a -- | Runs a Chunk writer and returns the written log. execChunkWriter :: Writer [Chunk] a -> String -- | Runs a Chunk writer transformer, combining them with -- combineChunks to form a single string. runChunkWriterT :: Monad m => WriterT [Chunk] m a -> m (a, String) -- | Runs a Chunk writer transformer and returns the monad's value. evalChunkWriterT :: Monad m => WriterT [Chunk] m a -> m a -- | Runs a Chunk writer transformer and returns the written log. execChunkWriterT :: Monad m => WriterT [Chunk] m a -> m String -- | Emits a single Chunk. say :: MonadWriter [Chunk] m => String -> m () -- | Emits a Chunk for each string in a list. says :: MonadWriter [Chunk] m => [String] -> m () -- | Emits an Identifier. sayIdentifier :: MonadWriter [Chunk] m => Identifier -> m () -- | sayVar name maybeParamNames t speaks a variable declaration -- of the form <type> <name>, where -- <name> is the given name, and <type> is -- rendered by giving maybeParamNames and t to -- sayType. -- -- This function is useful for generating variable declarations, -- declarations with assignments, and function prototypes and -- definitions. sayVar :: MonadWriter [Chunk] m => String -> Maybe [String] -> Type -> m () -- | sayType maybeParamNames t renders t in C++ syntax. -- If t is a fnT, then maybeParamNames will -- provide variable names for parameters, if present. sayType :: MonadWriter [Chunk] m => Maybe [String] -> Type -> m () -- | A driver for a command-line interface to a generator. -- -- A simple Main.hs for a generator can simply be: -- --
--   import Foreign.Hoppy.Generator.Main (defaultMain)
--   import Foreign.Hoppy.Generator.Spec (ErrorMsg, Interface, interface)
--   
--   interfaceResult :: Either ErrorMsg Interface
--   interfaceResult = interface ...
--   
--   main :: IO ()
--   main = defaultMain interfaceResult
--   
module Foreign.Hoppy.Generator.Main -- | Actions that can be requested of the program. data Action -- | Sets the interface that will be used for subsequent actions. SelectInterface :: String -> Action -- | Lists the interfaces compiled into the generator. ListInterfaces :: Action -- | Lists the generated files in C++ bindings. ListCppFiles :: Action -- | Lists the generated files in Haskell bindings. ListHsFiles :: Action -- | Generates C++ wrappers for an interface in the given location. GenCpp :: FilePath -> Action -- | Generates Haskell bindings for an interface in the given location. GenHaskell :: FilePath -> Action -- | This provides a simple main function for a generator. Define -- your main as: -- --
--   main = defaultMain $ interface ...
--   
-- -- Refer to run for how to use the command-line interface. Use -- defaultMain' if you want to include multiple interfaces in your -- generator. defaultMain :: Either String Interface -> IO () -- | This is a version of defaultMain that accepts multiple -- interfaces. defaultMain' :: [Either String Interface] -> IO () -- | run interfaces args runs the driver with the command-line -- arguments from args against the listed interfaces, and -- returns the list of actions performed. -- -- The recognized arguments are listed below. The exact forms shown are -- required; the --long-arg=value style is not supported. -- -- run :: [Interface] -> [String] -> IO [Action] -- | Utilities for conditional compilation of parts of interfaces. -- -- This module provides wrappers around Maybe and catMaybes -- so that you can write code such as: -- --
--   myClass =
--     makeClass ...
--     [ ...ctors... ] $
--     collect
--     [ just $ mkMethod "foo" ...
--     , test (apiVersion >= [1, 2]) $ mkMethod "bar" ...
--     , test featureBaz $ mkMethod "baz" ...
--     ]
--   
module Foreign.Hoppy.Generator.Version -- | Placeholder Maybe-like type that may be more general in the -- future. type Filtered = Maybe -- | Filters a list of Filtered values down to the elements that are -- actually present. collect :: [Filtered a] -> [a] -- | A Filtered value that is always absent. none :: Filtered a -- | Returns a Filtered value that is always present. just :: a -> Filtered a -- | Returns a Filtered value that is only present if the boolean is -- true. test :: Bool -> a -> Filtered a -- | Versions of the C++ standard. data CppVersion Cpp1998 :: CppVersion Cpp2011 :: CppVersion Cpp2014 :: CppVersion -- | The CppVersion chosen when one is not explicitly requested. -- This is Cpp2011. defaultCppVersion :: CppVersion -- | The active version of the C++ standard. This looks to the -- HOPPY_CPP_STD environment variable, and accepts the values -- c++98, c++11, and c++14, which map to the -- corresponding CppVersion values. If a value other than these is -- set, then a warning is printed and the default is used. If no value is -- set, the default is used. -- -- This uses unsafePerformIO internally and won't cope with a -- changing environment. activeCppVersion :: CppVersion instance GHC.Show.Show Foreign.Hoppy.Generator.Version.CppVersion instance GHC.Classes.Ord Foreign.Hoppy.Generator.Version.CppVersion instance GHC.Classes.Eq Foreign.Hoppy.Generator.Version.CppVersion instance GHC.Enum.Enum Foreign.Hoppy.Generator.Version.CppVersion instance GHC.Enum.Bounded Foreign.Hoppy.Generator.Version.CppVersion