-- 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.8.0 -- | Data types for compilers and functions for invoking them. module Foreign.Hoppy.Generator.Compiler -- | A compiler that exists on the system for compiling C++ code. class Show a => Compiler a -- | compileProgram compiler infile outfile invokes the given -- compiler in the input file, to produce the output file. If the -- compiler fails or can't be called for whatever reason, then an error -- message is printed to standard error, and false is returned. compileProgram :: Compiler a => a -> FilePath -> FilePath -> IO Bool -- | Modifies the compiler to prepend the given paths to the header search -- path. prependIncludePath :: Compiler a => [FilePath] -> a -> a -- | An existential data type for Compilers. data SomeCompiler SomeCompiler :: a -> SomeCompiler -- | A compiler that can compile a source file into a binary with a single -- program invocation. -- -- Within the strings in this data type, including the program path, all -- occurences of {in} and {out} are expanded to the -- input and desired output files, respectively. data SimpleCompiler SimpleCompiler :: FilePath -> [String] -> SimpleCompiler -- | The name of the compiler program to call. Lookup is subject to the -- regular search path rules of your operating system. [scProgram] :: SimpleCompiler -> FilePath -- | Arguments to pass to the compiler. Each string is passed as a separate -- argument. No further word splitting is done. [scArguments] :: SimpleCompiler -> [String] -- | Adds arguments to the start of a compiler's argument list. prependArguments :: [String] -> SimpleCompiler -> SimpleCompiler -- | Adds arguments to the end of a compiler's argument list. appendArguments :: [String] -> SimpleCompiler -> SimpleCompiler -- | Modifies a SimpleCompiler based on environment variables. -- -- If CXX is set and non-empty, it will override the compiler's -- scProgram. -- -- If CXXFLAGS is set and non-empty, it will be split into words -- and each word will be prepended as an argument to scArguments. -- Quoting is not supported. overrideCompilerFromEnvironment :: SimpleCompiler -> IO SimpleCompiler -- | A Compiler that allows plugging arbitary logic into the -- compilation process. data CustomCompiler CustomCompiler :: String -> (CustomCompiler -> FilePath -> FilePath -> IO Bool) -> [FilePath] -> CustomCompiler -- | A label to display when the compiler is shown. The string is -- "<CustomCompiler " ++ label ++ ">". [ccLabel] :: CustomCompiler -> String -- | Given a source file path and an output path, compiles the source file, -- producing a binary at the output path. Returns true on success. Logs -- to standard error and returns false on failure. -- -- This should inspect the compiler argument to make use of its -- ccHeaderSearchPath. -- -- The first argument is the CustomCompiler object that this -- function was pulled out of. This is passed in explicitly by -- compileProgram because due to the presence of -- prependIncludePath it's not always possible to have access to -- the final compiler object ahead of time. [ccCompile] :: CustomCompiler -> CustomCompiler -> FilePath -> FilePath -> IO Bool -- | Paths to be searched for C++ header files, in addition to the -- compiler's default search directories. [ccHeaderSearchPath] :: CustomCompiler -> [FilePath] -- | The default compiler, used by an Interface that doesn't specify -- its own. This will be gppCompiler, however if the environment -- variables CXX or CXXFLAGS are set and nonempty, they -- will be used. CXX will override the path to the compiler -- used, and CXXFLAGS will be split on spaces and appended to -- the compiler's argument list. -- -- Specifically, this is defined as: -- --
--   unsafePerformIO $ overrideCompilerFromEnvironment gppCompiler
--   
defaultCompiler :: SimpleCompiler -- | The GNU C++ compiler, invoked as g++ -o {out} {in}. gppCompiler :: SimpleCompiler instance GHC.Show.Show Foreign.Hoppy.Generator.Compiler.CustomCompiler instance Foreign.Hoppy.Generator.Compiler.Compiler Foreign.Hoppy.Generator.Compiler.CustomCompiler instance GHC.Show.Show Foreign.Hoppy.Generator.Compiler.SimpleCompiler instance Foreign.Hoppy.Generator.Compiler.Compiler Foreign.Hoppy.Generator.Compiler.SimpleCompiler instance GHC.Show.Show Foreign.Hoppy.Generator.Compiler.SomeCompiler instance Foreign.Hoppy.Generator.Compiler.Compiler Foreign.Hoppy.Generator.Compiler.SomeCompiler -- | Support for specifying overrides of values based on parameters. -- -- For example, an entity may have a name that you want to override on a -- per-language basis. A single value like this may be represented as a -- WithOverrides Language Name value. Such a value will -- have a default name, as well as zero or more overrides, keyed by -- Language. -- -- A MapWithOverrides type is also provided for ease of overriding -- values inside of a map. module Foreign.Hoppy.Generator.Override -- | Represents a default value of type v with optional overrides -- keyed by parameter type p. The type p must have an -- Ord instance. data WithOverrides p v -- | Creates a WithOverrides with the given default value -- v, and no overridden values. plain :: v -> WithOverrides p v -- | Creates a WithOverrides with the given default value -- v, and overridden values in the map. overridden :: v -> Map p v -> WithOverrides p v -- | The default, unoverriden value for the WithOverrides. Lookups -- on the override will return this value a given parameter doesn't have -- an override. unoverriddenValue :: WithOverrides p v -> v -- | Any overridden values that have been added to the -- WithOverrides. overriddenValues :: WithOverrides p v -> Map p v -- | Represents a map from k values to v values, where -- each entry can be overridden based on parameter p. A key is -- either present with a default value and possibly some overridden -- values, or it is completely absent -- it is not possible for a key to -- have overridden values but no default value. data MapWithOverrides p k v -- | Converts a plain map to a MapWithOverrides without any -- overrides. plainMap :: Map k v -> MapWithOverrides p k v -- | Direct constructor for MapWithOverrides. mapWithOverrides :: Map k (WithOverrides p v) -> MapWithOverrides p k v -- | Adds a collection of overrides v for multiple keys -- k, all under a single parameter p, to a -- MapWithOverrides. -- -- It is an error for a parameter to override a key that is not present -- in the defaults map. addOverrideMap :: (Ord p, Ord k, Show p, Show k) => p -> Map k v -> MapWithOverrides p k v -> MapWithOverrides p k v -- | Adds overrides v for multiple keys k under multiple -- parameters p to a MapWithOverrides. -- -- It is an error for a parameter to override a key that is not present -- in the defaults map. addOverrideMaps :: (Ord p, Ord k, Show p, Show k) => Map p (Map k v) -> MapWithOverrides p k v -> MapWithOverrides p k v -- | Constructs a MapWithOverrides from a map of default values and -- a bunch of parameter-specific maps overlaid on top of it. -- -- It is an error for a parameter to override a key that is not present -- in the defaults map. applyOverrideMaps :: (Ord p, Ord k, Show p, Show k) => Map p (Map k v) -> Map k v -> MapWithOverrides p k v -- | Adds an override v for key k under parameter -- p to a MapWithOverrides. -- -- It is an error for a parameter to override a key that is not present -- in the defaults map. insertMapOverride :: (Ord p, Ord k, Show p, Show k) => p -> k -> v -> MapWithOverrides p k v -> MapWithOverrides p k v -- | Looks up a value for k in the given MapWithOverrides, -- with the possibility that the value is overridden by the parameter -- p. overriddenMapLookup :: (Ord p, Ord k) => p -> k -> MapWithOverrides p k v -> Maybe v -- | 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 -- | A const version of another type. constT :: Type -> Type -- | C++ void, Haskell (). voidT :: Type -- | A pointer to another type. ptrT :: Type -> Type -- | A reference to another type. refT :: Type -> Type fnT :: [Type] -> Type -> Type fnT' :: [Parameter] -> Type -> Type -- | C++ bool, Haskell Bool. -- -- C++ has sizeof(bool) == 1, whereas Haskell can > 1, so we have to -- convert. boolT :: Type -- | C++ bool, Haskell CBool. boolT' :: Type -- | C++ char, Haskell CChar. charT :: Type -- | C++ unsigned char, Haskell CUChar. ucharT :: Type -- | C++ wchar_t, Haskell CWchar. wcharT :: Type -- | C++ short int, Haskell CShort. shortT :: Type -- | C++ unsigned short int, Haskell CUShort. ushortT :: Type -- | C++ int, Haskell Int. See also intT'. intT :: Type -- | C++ int, Haskell CInt. See also intT. 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 Float. See also floatT'. floatT :: Type -- | C++ float, Haskell CFloat. See also floatT. floatT' :: Type -- | C++ double, Haskell Double. See also doubleT'. doubleT :: Type -- | C++ double, Haskell CDouble. See also doubleT. 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 -- | Builds a new numeric type definition. -- -- For convenience, convertByCoercingIntegral and -- convertByCoercingFloating may be used as conversion methods, -- for both ConversionMethod arguments this function takes. makeNumericType :: String -> Reqs -> Generator HsType -> Maybe (Generator HsType) -> ConversionMethod (Generator ()) -> ConversionMethod (Generator ()) -> Type -- | Conversion method for passing a numeric values to and from Haskell by -- using Foreign.Hoppy.Runtime.coerceIntegral. convertByCoercingIntegral :: ConversionMethod (Generator ()) -- | Conversion method for passing a numeric values to and from Haskell by -- using realToFrac. convertByCoercingFloating :: ConversionMethod (Generator ()) -- | Constructs a type from a specification of how to convert values. manualT :: ConversionSpec -> Type callbackT :: Callback -> Type enumT :: CppEnum -> 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 -- | Module for computed data for an interface. module Foreign.Hoppy.Generator.Spec.Computed -- | Holds "computed data" for an interface. This is data that is -- calculated by Hoppy, beyond what is directly specified in the -- interface. data ComputedInterfaceData ComputedInterfaceData :: String -> Map ExtName EvaluatedEnumData -> ComputedInterfaceData -- | The name of the interface. [computedInterfaceName] :: ComputedInterfaceData -> String -- | Evaluated numeric types and values for all enums in the interface. [evaluatedEnumMap] :: ComputedInterfaceData -> Map ExtName EvaluatedEnumData -- | Information about the enum that has been completed beyond what the -- interface definition provides, possibly by building actual C++ code. data EvaluatedEnumData EvaluatedEnumData :: NumericTypeInfo -> EvaluatedEnumValueMap -> EvaluatedEnumData -- | The numeric type that C++ uses to hold the enum's values, or an -- equivalently-sized type. [evaluatedEnumNumericType] :: EvaluatedEnumData -> NumericTypeInfo -- | Calculated values for all of the enum's entries. [evaluatedEnumValueMap] :: EvaluatedEnumData -> EvaluatedEnumValueMap -- | Contains the numeric values for each of the entries in a C++ enum. type EvaluatedEnumValueMap = Map [String] Integer -- | Returns the map containing the calculated values for all entries in -- the enum with the given ExtName. This requires hooks to have -- been run. getEvaluatedEnumData :: HasCallStack => ComputedInterfaceData -> ExtName -> EvaluatedEnumData -- | Bound information about numeric types. data NumericTypeInfo -- | The numeric data type described by the record. numType :: NumericTypeInfo -> Type -- | The number of bytes in a value of the type. numBytes :: NumericTypeInfo -> Int -- | The lowest (most negative) value representable by the type. numMinBound :: NumericTypeInfo -> Integer -- | The highest (most positive) value representable by the type. numMaxBound :: NumericTypeInfo -> Integer -- | Searches the list of known numeric types usable for enum values, and -- returns the record for the given type. findNumericTypeInfo :: Type -> Maybe NumericTypeInfo -- | Selects the preferred numeric type for holding numeric values in the -- given range. pickNumericType :: Int -> Integer -> Integer -> Maybe NumericTypeInfo instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Computed.EvaluatedEnumData instance GHC.Read.Read Foreign.Hoppy.Generator.Spec.Computed.EvaluatedEnumData instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Computed.NumericTypeInfo instance GHC.Read.Read Foreign.Hoppy.Generator.Spec.Computed.NumericTypeInfo -- | 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 -> ComputedInterfaceData -> Module -> Generator a -> Either ErrorMsg (Partial, a) -- | Runs a generator action and returns the its value. evalGenerator :: Interface -> ComputedInterfaceData -> Module -> Generator a -> Either ErrorMsg a -- | Runs a generator action and returns its output. execGenerator :: Interface -> ComputedInterfaceData -> Module -> Generator a -> Either ErrorMsg Partial -- | Converts a Partial into a complete Haskell module. renderPartial :: Partial -> String -- | Context information for generating Haskell code. data Env Env :: Interface -> ComputedInterfaceData -> Module -> String -> Env [envInterface] :: Env -> Interface [envComputedInterfaceData] :: Env -> ComputedInterfaceData [envModule] :: Env -> Module [envModuleName] :: Env -> String -- | Returns the currently generating interface. askInterface :: Generator Interface -- | Returns the computed data for the currently generating interface. askComputedInterfaceData :: Generator ComputedInterfaceData -- | 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 () -- | The section of code that Hoppy is generating, for an export. data SayExportMode -- | Hoppy is generating foreign import statements for an export. -- This is separate from the main SayExportDecls phase because -- foreign import statements are emitted directly by a Generator, -- and these need to appear earlier in the code. SayExportForeignImports :: SayExportMode -- | Hoppy is generating Haskell code to bind to the export. This is the -- main step of Haskell code generation for an export. -- -- Here, imports of Haskell modules should be added with -- addImports rather than emitting an import statement -- yourself in the foreign import step. addExtNameModule may be -- used to import and reference the Haskell module of another export. SayExportDecls :: SayExportMode -- | If Hoppy needs to generate hs-boot files to break circular -- dependences between generated modules, then for each export in each -- module involved in a cycle, it will call the generator in this mode to -- produce hs-boot code. This code should provide a minimal -- declaration of Haskell entities generated by SayExportDecls, -- without providing any implementation. -- -- For information on the special format of hs-boot files, see -- the GHC User's Guide. SayExportBoot :: SayExportMode -- | 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 () -- | Looks up the module that exports an external name. Throws an error if -- the external name is not exported. getExtNameModule :: ExtName -> Generator Module -- | Used like addExtNameModule extName hsEntity. -- hsEntity is a name in Haskell code that is generated from the -- definition of extName, and thus lives in extName's -- module. This function adds imports and returns a qualified name as -- necessary to refer to the given entity. addExtNameModule :: ExtName -> String -> Generator String -- | Constructs Haskell names from external names. Returns a name that is a -- suitable Haskell type name for the external name, and if given -- Const, then with "Const" appended. toHsTypeName :: Constness -> ExtName -> Generator String -- | Pure version of toHsTypeName that doesn't create a qualified -- name. toHsTypeName' :: Constness -> ExtName -> 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 -- | Combines the given exception handlers (from a particular exported -- entity) with the handlers from the current module and interface. The -- given handlers have highest precedence, followed by module handlers, -- followed by interface handlers. getEffectiveExceptionHandlers :: ExceptionHandlers -> Generator ExceptionHandlers -- | 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.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.Show.Show Foreign.Hoppy.Generator.Language.Haskell.SayExportMode instance GHC.Classes.Eq Foreign.Hoppy.Generator.Language.Haskell.SayExportMode instance GHC.Show.Show Foreign.Hoppy.Generator.Language.Haskell.HsTypeSide instance GHC.Classes.Eq Foreign.Hoppy.Generator.Language.Haskell.HsTypeSide instance GHC.Classes.Eq Foreign.Hoppy.Generator.Language.Haskell.Partial instance GHC.Classes.Ord Foreign.Hoppy.Generator.Language.Haskell.Partial instance GHC.Base.Semigroup Foreign.Hoppy.Generator.Language.Haskell.Output instance GHC.Base.Monoid Foreign.Hoppy.Generator.Language.Haskell.Output -- | Shared portion of the C++ code generator. Usable by binding -- definitions. module Foreign.Hoppy.Generator.Language.Cpp -- | A generator monad for C++ code. -- -- TODO This should not simply be a type synonym. type Generator = ReaderT Env (WriterT [Chunk] (Either ErrorMsg)) -- | Context information for generating C++ code. data Env -- | Runs a generator action and returns its output, or an error message if -- unsuccessful. execGenerator :: Interface -> ComputedInterfaceData -> Module -> Maybe String -> Generator a -> Either ErrorMsg String -- | Adds #include statements to the includes block generated at -- the top of the currently generating file. addIncludes :: MonadWriter [Chunk] m => [Include] -> m () -- | Adds an #include statement to the includes block generated at -- the top of the currently generating file. addInclude :: MonadWriter [Chunk] m => Include -> m () -- | Adds requirements (Reqs i.e. C++ includes) to the includes -- block generated at the top of the currently generating file. -- -- Have to call this addReqsM, addReqs is taken by -- HasReqs. addReqsM :: MonadWriter [Chunk] m => Reqs -> m () -- | Returns the currently generating interface. askInterface :: MonadReader Env m => m Interface -- | Returns the computed data for the currently generating interface. askComputedInterfaceData :: Generator ComputedInterfaceData -- | Returns the currently generating module. askModule :: MonadReader Env m => m Module -- | Halts generation and returns the given error message. abort :: ErrorMsg -> Generator a -- | Constructs a C++ identifier by combining a list of strings with -- __. makeCppName :: [String] -> String -- | Returns the C++ binding function name for an external name. externalNameToCpp :: ExtName -> 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, -- together with a set of includes. The only requirement is that chunk's -- code boundaries are also C++ token boundaries, because the generator -- monad automates the process of inserting whitespace between chunk -- boundaries where necessary. data Chunk Chunk :: !String -> !Set Include -> Chunk [chunkContents] :: Chunk -> !String [chunkIncludes] :: Chunk -> !Set Include -- | Builds a Chunk that contains the given code string. codeChunk :: String -> Chunk -- | Builds a Chunk that contains the given includes. includesChunk :: Set Include -> Chunk -- | Runs a Chunk writer, combining them with combineChunks -- to form a single string. runChunkWriter :: Writer [Chunk] a -> (a, Chunk) -- | 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 -> Chunk -- | Runs a Chunk writer transformer, combining them with -- combineChunks to form a single string. runChunkWriterT :: Monad m => WriterT [Chunk] m a -> m (a, Chunk) -- | 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 Chunk -- | The section of code that Hoppy is generating, for an export. data SayExportMode -- | Hoppy is generating the C++ source file for a module. The generator -- should emit C++ definitions that will be imported over foreign -- language's FFIs. This is the main place for code generation in C++ -- bindings. SaySource :: SayExportMode -- | Hoppy is generating the C++ header file for a module. The generator -- should emit C++ declarations that can be #included during the -- source file generation of other exportable entities, in order to refer -- to the current entity. If it is not possible for other entities to -- refer to this one, then nothing needs to be generated. SayHeader :: SayExportMode -- | 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 () -- | Renders an Identifier to a string. renderIdentifier :: Identifier -> String -- | 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 () -- | Renders a C++ function. sayFunction :: String -> [String] -> Type -> Maybe (Generator ()) -> Generator () -- | Returns a Type iff there is a C type distinct from the given -- C++ type that should be used for conversion. -- -- This returns Nothing for Internal_TManual. TManual -- needs special handling. typeToCType :: Type -> Generator (Maybe Type) -- | Returns the requirements to refer to a type from C++ code. This is a -- monadic function so that it has access to the environment, but it does -- not emit any code. typeReqs :: Type -> Generator Reqs -- | Looks up the module exporting the given external name in the current -- interface. abort is called if the external name is not found. findExportModule :: ExtName -> Generator Module -- | Combines the given exception handlers (from a particular exported -- entity) with the handlers from the current module and interface. The -- given handlers have highest precedence, followed by module handlers, -- followed by interface handlers. getEffectiveExceptionHandlers :: ExceptionHandlers -> Generator ExceptionHandlers -- | Interface for defining bindings to C++ functions. module Foreign.Hoppy.Generator.Spec.Function -- | 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 -- | A function taking parameters and returning a value (or voidT). -- Function pointers must wrap a fnT in a ptrT. -- -- See also fnT' which accepts parameter information. fnT :: [Type] -> Type -> Type -- | A version of fnT that accepts additional information about -- parameters. fnT' :: [Parameter] -> Type -> Type -- | Creates a binding for a C++ function. makeFn :: (IsFnName Identifier name, IsParameter p) => name -> Maybe ExtName -> Purity -> [p] -> Type -> Function -- | The function's external name. fnExtName :: Function -> ExtName -- | The identifier used to call the function. fnCName :: Function -> FnName Identifier -- | Whether the function is pure. fnPurity :: Function -> Purity -- | The function's parameters. fnParams :: Function -> [Parameter] -- | The function's return type. fnReturn :: Function -> Type -- | Requirements for bindings to access this function. fnReqs :: Function -> Reqs -- | The function's addendum. fnAddendum :: Function -> Addendum -- | Exceptions that the function might throw. fnExceptionHandlers :: Function -> ExceptionHandlers -- | The direction between languages in which a value is being passed. data CallDirection -- | Haskell code is calling out to C++. ToCpp :: CallDirection -- | C++ is invoking a callback. FromCpp :: CallDirection -- | The name of a function to call. data CppCallType -- | A call to the given operator, for example x++, x * -- y, a[i]. CallOp :: Operator -> CppCallType -- | A call to the function whose name is emitted by the given action. CallFn :: Generator () -> CppCallType -- | Not a function call, but a read from a variable whose name is emitted -- by the given action. VarRead :: Generator () -> CppCallType -- | Not a function call, but a write to a variable whose name is emitted -- by the given action. VarWrite :: Generator () -> CppCallType -- | Generates code to marshal a value between a C++ type and the -- intermediate type to be used over the FFI. If dir is -- ToCpp, then we are a C++ function reading an argument from -- foreign code. If dir is FromCpp, then we are invoking -- a foreign callback. sayCppArgRead :: CallDirection -> (Int, Type, Maybe Type) -> Generator () -- | Prints a comma-separated list of the argument names used for C++ -- gateway functions. The number specifies how many names to print. sayCppArgNames :: Int -> Generator () -- | Generates a C++ wrapper function for calling a C++ function (or -- method, or reading from or writing to a variable). The generated -- function handles C++-side marshalling of values and propagating -- exceptions as requested. -- -- See also sayHsExportFn. sayCppExportFn :: ExtName -> CppCallType -> Maybe Type -> [Parameter] -> Type -> ExceptionHandlers -> Bool -> Generator () -- | Generates a Haskell wrapper function for calling a C++ function (or -- method, or reading from or writing to a variable, as with -- sayCppExportFn). The generated function handles Haskell-side -- marshalling of values and propagating exceptions as requested. sayHsExportFn :: SayExportMode -> ExtName -> ExtName -> Purity -> [Parameter] -> Type -> ExceptionHandlers -> Generator () -- | Generates Haskell code to perform marshalling of a function's argument -- in a specified direction. -- -- This function either generates a line or lines such that subsequent -- lines can refer to the output binding. The final line is either -- terminated with -- --
--   ... $ \value ->
--   
-- -- or -- --
--   let ... in
--   
-- -- so that precedence is not an issue. sayHsArgProcessing :: CallDirection -> Type -> String -> String -> Generator () -- | Note that the CallDirection is the direction of the call, not -- the direction of the return. ToCpp means we're returning to the -- foreign language, FromCpp means we're returning from it. sayHsCallAndProcessReturn :: CallDirection -> Type -> [String] -> Generator () instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Function.CallDirection instance GHC.Classes.Eq Foreign.Hoppy.Generator.Spec.Function.Function instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Function.Function instance Foreign.Hoppy.Generator.Spec.Base.Exportable Foreign.Hoppy.Generator.Spec.Function.Function instance Foreign.Hoppy.Generator.Spec.Base.HasExtNames Foreign.Hoppy.Generator.Spec.Function.Function instance Foreign.Hoppy.Generator.Spec.Base.HasReqs Foreign.Hoppy.Generator.Spec.Function.Function instance Foreign.Hoppy.Generator.Spec.Base.HasAddendum Foreign.Hoppy.Generator.Spec.Function.Function instance Foreign.Hoppy.Generator.Spec.Base.HandlesExceptions Foreign.Hoppy.Generator.Spec.Function.Function -- | Interface for defining bindings to C++ classes. module Foreign.Hoppy.Generator.Spec.Class -- | 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 class's external name. classExtName :: Class -> ExtName -- | The identifier used to refer to the class. classIdentifier :: Class -> Identifier -- | Requirements for bindings to access this class. classReqs :: Class -> Reqs -- | The class's addendum. classAddendum :: Class -> Addendum -- | The class's public superclasses. classSuperclasses :: 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 -- | 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 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 -- | 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 -- | 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 -- | Returns all of the names in a ClassEntity within the -- corresponding Class. classEntityExtNames :: Class -> ClassEntity -> [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 -- | 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 :: IsParameter p => ExtName -> [p] -> ClassEntity -- | The unwrapped version of makeCtor. makeCtor_ :: IsParameter p => ExtName -> [p] -> 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 :: IsParameter p => String -> [p] -> ClassEntity -- | The unwrapped version of mkCtor. mkCtor_ :: IsParameter p => String -> [p] -> Ctor -- | The constructor's external name. ctorExtName :: Ctor -> ExtName -- | The constructor's parameters. ctorParams :: Ctor -> [Parameter] -- | 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 -- | 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 static. data Staticness Nonstatic :: Staticness Static :: Staticness -- | 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 -- | 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 -> ClassEntity -- | The unwrapped version of makeMethod. makeMethod_ :: (IsFnName String name, IsParameter p) => name -> ExtName -> MethodApplicability -> Purity -> [p] -> 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, IsParameter p) => name -> String -> MethodApplicability -> Purity -> [p] -> Type -> ClassEntity -- | The unwrapped version of makeFnMethod. makeFnMethod_ :: (IsFnName Identifier name, IsParameter p) => name -> String -> MethodApplicability -> Purity -> [p] -> 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, IsParameter p) => name -> [p] -> Type -> ClassEntity -- | The unwrapped version of mkMethod. mkMethod_ :: (IsFnName String name, IsParameter p) => name -> [p] -> 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, IsParameter p) => name -> String -> [p] -> Type -> ClassEntity -- | The unwrapped version of mkMethod'. mkMethod'_ :: (IsFnName String name, IsParameter p) => name -> String -> [p] -> 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, IsParameter p) => name -> [p] -> Type -> ClassEntity -- | The unwrapped version of mkConstMethod. mkConstMethod_ :: (IsFnName String name, IsParameter p) => name -> [p] -> 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, IsParameter p) => name -> String -> [p] -> Type -> ClassEntity -- | The unwrapped version of mkConstMethod'. mkConstMethod'_ :: (IsFnName String name, IsParameter p) => name -> String -> [p] -> 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, IsParameter p) => name -> [p] -> Type -> ClassEntity -- | The unwrapped version of mkStaticMethod. mkStaticMethod_ :: (IsFnName String name, IsParameter p) => name -> [p] -> 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, IsParameter p) => name -> String -> [p] -> Type -> ClassEntity -- | The unwrapped version of mkStaticMethod'. mkStaticMethod'_ :: (IsFnName String name, IsParameter p) => name -> String -> [p] -> Type -> Method -- | The method's external name. methodExtName :: Method -> ExtName -- | The underlying code that the binding calls. methodImpl :: Method -> MethodImpl -- | How the method is associated to its class. methodApplicability :: Method -> MethodApplicability -- | 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 -- | Whether the method is pure. methodPurity :: Method -> Purity -- | The method's parameters. methodParams :: Method -> [Parameter] -- | The method's return type. methodReturn :: Method -> Type -- | Exceptions that the method might throw. methodExceptionHandlers :: Method -> ExceptionHandlers -- | 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 -- | 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 :: HasCallStack => (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 ()) -- | Replaces a class's classHaskellConversion with a given value. classSetHaskellConversion :: ClassHaskellConversion -> Class -> Class -- | 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 -- | Searches a class for a copy constructor, returning it if found. classFindCopyCtor :: Class -> Maybe Ctor -- | Generates C++ gateway functions (via sayCppExportFn) for -- getting and setting a variable (possibly a class variable). sayCppExportVar :: Type -> Maybe (Type, Type) -> Bool -> ExtName -> ExtName -> Generator () -> Generator () -- | Generates Haskell gateway functions (via sayHsExportFn) for -- getting and setting a variable (possibly a class variable). sayHsExportVar :: SayExportMode -> Type -> Maybe Class -> Bool -> ExtName -> ExtName -> ExtName -> ExtName -> Generator () instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Class.MethodImpl instance GHC.Classes.Eq Foreign.Hoppy.Generator.Spec.Class.MethodImpl instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Class.MethodApplicability instance GHC.Classes.Eq Foreign.Hoppy.Generator.Spec.Class.MethodApplicability instance GHC.Enum.Enum Foreign.Hoppy.Generator.Spec.Class.MethodApplicability instance GHC.Enum.Bounded Foreign.Hoppy.Generator.Spec.Class.MethodApplicability instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Class.Staticness instance GHC.Classes.Eq Foreign.Hoppy.Generator.Spec.Class.Staticness instance GHC.Enum.Enum Foreign.Hoppy.Generator.Spec.Class.Staticness instance GHC.Enum.Bounded Foreign.Hoppy.Generator.Spec.Class.Staticness instance GHC.Classes.Eq Foreign.Hoppy.Generator.Spec.Class.Class instance GHC.Classes.Ord Foreign.Hoppy.Generator.Spec.Class.Class instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Class.Class instance Foreign.Hoppy.Generator.Spec.Base.Exportable Foreign.Hoppy.Generator.Spec.Class.Class instance Foreign.Hoppy.Generator.Spec.Base.HasExtNames Foreign.Hoppy.Generator.Spec.Class.Class instance Foreign.Hoppy.Generator.Spec.Base.HasReqs Foreign.Hoppy.Generator.Spec.Class.Class instance Foreign.Hoppy.Generator.Spec.Base.HasAddendum Foreign.Hoppy.Generator.Spec.Class.Class instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Class.ClassVariable instance Foreign.Hoppy.Generator.Spec.Class.IsClassEntity Foreign.Hoppy.Generator.Spec.Class.ClassVariable instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Class.Method instance Foreign.Hoppy.Generator.Spec.Base.HandlesExceptions Foreign.Hoppy.Generator.Spec.Class.Method instance Foreign.Hoppy.Generator.Spec.Class.IsClassEntity Foreign.Hoppy.Generator.Spec.Class.Method instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Class.Ctor instance Foreign.Hoppy.Generator.Spec.Base.HandlesExceptions Foreign.Hoppy.Generator.Spec.Class.Ctor instance Foreign.Hoppy.Generator.Spec.Class.IsClassEntity Foreign.Hoppy.Generator.Spec.Class.Ctor -- | Interface for defining bindings to C++ variables. module Foreign.Hoppy.Generator.Spec.Variable -- | 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 variable's external name. varExtName :: Variable -> ExtName -- | The identifier used to refer to the variable. varIdentifier :: Variable -> Identifier -- | 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 -- | The variable's addendum. varAddendum :: Variable -> Addendum -- | 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 instance GHC.Classes.Eq Foreign.Hoppy.Generator.Spec.Variable.Variable instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Variable.Variable instance Foreign.Hoppy.Generator.Spec.Base.Exportable Foreign.Hoppy.Generator.Spec.Variable.Variable instance Foreign.Hoppy.Generator.Spec.Base.HasExtNames Foreign.Hoppy.Generator.Spec.Variable.Variable instance Foreign.Hoppy.Generator.Spec.Base.HasReqs Foreign.Hoppy.Generator.Spec.Variable.Variable instance Foreign.Hoppy.Generator.Spec.Base.HasAddendum Foreign.Hoppy.Generator.Spec.Variable.Variable -- | 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 -- | Interface for defining foreign language callbacks. module Foreign.Hoppy.Generator.Spec.Callback -- | 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 -- | Constructs a type value for a callback. callbackT :: Callback -> Type -- | Creates a binding for constructing callbacks into foreign code. makeCallback :: IsParameter p => ExtName -> [p] -> Type -> Callback -- | The callback's external name. callbackExtName :: Callback -> ExtName -- | The callback's parameters. callbackParams :: Callback -> [Parameter] -- | The callback's return type. callbackReturn :: Callback -> Type -- | Extra requirements for the callback. callbackReqs :: Callback -> Reqs -- | The callback's addendum. callbackAddendum :: Callback -> Addendum -- | 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 -- | Sets whether a callback supports handling thrown C++ exceptions and -- passing them into C++. callbackSetThrows :: Bool -> Callback -> Callback -- | Constructs the function type for a callback. A callback that throws -- has additional parameters. -- -- Keep this in sync with hsCallbackToTFn. cppCallbackToTFn :: Callback -> Generator Type -- | Returns the name of the outer, copyable C++ class for a callback. callbackClassName :: Callback -> String -- | Returns the name of the internal, non-copyable implementation C++ -- 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 -- | 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 cppCallbackToTFn. hsCallbackToTFn :: HsTypeSide -> Callback -> Generator Type -- | 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 instance GHC.Classes.Eq Foreign.Hoppy.Generator.Spec.Callback.Callback instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Callback.Callback instance Foreign.Hoppy.Generator.Spec.Base.Exportable Foreign.Hoppy.Generator.Spec.Callback.Callback instance Foreign.Hoppy.Generator.Spec.Base.HasExtNames Foreign.Hoppy.Generator.Spec.Callback.Callback instance Foreign.Hoppy.Generator.Spec.Base.HasReqs Foreign.Hoppy.Generator.Spec.Callback.Callback instance Foreign.Hoppy.Generator.Spec.Base.HasAddendum Foreign.Hoppy.Generator.Spec.Callback.Callback -- | Miscellaneous utilities that may be useful in Hoppy generators. module Foreign.Hoppy.Generator.Util -- | Splits a C++ identifier string into multiple words, doing smart -- inspection of the case convention of the string. This supports -- snake_case and CONSTANT_CASE, and recognition of -- camelCase, including when acronyms are uppercased -- ("HTMLElement" gives ["HTML", "Element"]). Numbers -- are treated as their own words, and non-alphanumeric characters are -- treated as word separators and dropped. splitIntoWords :: String -> [String] -- | Creates a temporary file whose name is based on the given template -- string, and runs the given function with the path to the file. The -- file is deleted when the function completes, if the boolean that the -- function returns (or, in case of an exception, the boolean that was -- passed directly to withTempFile) is true. withTempFile :: String -> Bool -> (FilePath -> Handle -> IO (Bool, a)) -> IO a -- | Creates a temporary directory whose name is based on the given -- template string, and runs the given function with the directory's -- path. The directory is deleted when the function completes, if the -- boolean that the function returns (or, in case of an exception, the -- boolean that was passed directly to withTempDirectory) is true. withTempDirectory :: String -> Bool -> (FilePath -> IO (Bool, a)) -> IO a -- | Interface for defining bindings to C++ enumerations. -- -- In generated Haskell code: -- -- An enum gets a single algebraic data type with data constructors for -- each of the values defined in the interface. If the enum has an -- unknown value name defined, then an additional data constructor is -- generated that holds a numeric value, and this constructor is used -- whenever numeric values for which no name is explicitly defined are -- encountered (otherwise, error is called). -- -- From the runtime module, a CppEnum instance is generated for -- the type, and if the enum is declared to permit bit operations, then a -- Bits instance is also generated. Eq and Ord -- instances are generated that compare numeric values. module Foreign.Hoppy.Generator.Spec.Enum -- | A C++ enum declaration. -- -- See EnumInfo. data CppEnum -- | Constructs a type value for an enum. enumT :: CppEnum -> Type -- | Creates a binding for a C++ enum. -- -- The numeric values of each of the enum's entries must be specified -- manually using this function. To have these determined automatically, -- instead use makeAutoEnum. makeEnum :: Identifier -> Maybe ExtName -> [(Integer, EnumEntryWords)] -> CppEnum -- | Creates a binding for a C++ enum. -- -- An enum created using this function will determine its entries' -- numeric values automatically when the generator is run, by compiling a -- temporary, autogenerated C++ helper program. -- -- This helper program needs to be able to access the C++ declaration of -- the enum. In addition to any includeStd or includeLocal -- requirements added to the enum for the generated C++ bindings to use, -- the interface's compiler (interfaceCompiler) will need -- to be able to use these includes to access the enum from C++ file -- built in a temporary directory. To add -I arguments or -- otherwise change the compiler, you can reconfigure the interface: -- --
--   myInterface =
--     interfaceSetCompiler (prependArguments ["-I" ++ pathToIncludes] defaultCompiler) $
--     interface ...
--   
-- -- See Foreign.Hoppy.Generator.Compiler. makeAutoEnum :: IsAutoEnumValue v => Identifier -> Maybe ExtName -> Scoped -> [v] -> CppEnum -- | Represents a mapping to an automatically evaluated C++ enum entry. -- -- The (EnumEntryWords, String) instance is the canonical -- one, with toAutoEnumValue defined as id. The string on -- the right is the C++ name of the entry, and the list of strings on the -- left are the words from which to generate foreign bindings' entry -- names. -- -- The String instance takes the C++ name of the entry, and -- splits it into words via splitIntoWords. class IsAutoEnumValue a toAutoEnumValue :: IsAutoEnumValue a => a -> (EnumEntryWords, String) -- | The enum's external name. enumExtName :: CppEnum -> ExtName -- | The identifier used to refer to the enum. enumIdentifier :: CppEnum -> Identifier -- | An optional, explicit numeric type provided for the enum's values, -- that matches what the C++ compiler uses. Hoppy will use Hooks -- to compute this automatically, if not given manually. This does not -- need to be provided. If absent (default), then Hoppy will calculate -- the enum's numeric type on its own, using a C++ compiler. If this is -- present however, Hoppy will use it, and additionally validate it -- against what the C++ compiler thinks, if validation is enabled (see -- interfaceValidateEnumTypes). enumNumericType :: CppEnum -> Maybe Type -- | Sets an explicit numeric type for the enum. See -- enumNumericType. enumSetNumericType :: Maybe Type -> CppEnum -> CppEnum -- | The numeric values and names of the enum entires. enumValues :: CppEnum -> EnumValueMap -- | Requirements for bindings to access this enum. Currently unused, but -- will be in the future. enumReqs :: CppEnum -> Reqs -- | The enum's addendum. enumAddendum :: CppEnum -> Addendum -- | The prefix applied to value names (enumValues) 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 -- | Adds overrides for some of an enum's entry names, in a specific -- language. enumAddEntryNameOverrides :: IsAutoEnumValue v => ForeignLanguage -> [(v, v)] -> CppEnum -> CppEnum -- | Retrieves the name for an enum entry in a specific foreign language. enumGetOverriddenEntryName :: ForeignLanguage -> CppEnum -> EnumEntryWords -> EnumEntryWords -- | Values that can be used as a name for an enum's unknown value entry. -- See enumUnknownValueEntry. class IsEnumUnknownValueEntry a -- | Converts a value to a list of words to use for an enum's unknown entry -- name. toEnumUnknownValueEntry :: IsEnumUnknownValueEntry a => a -> EnumEntryWords -- | A name (a list of words, a la the fields in EnumValueMap) for -- an optional fallback enum "entry" in generated bindings for holding -- unknown values. See enumUnknownValueEntryDefault. -- -- When this is a Just, then the generated foreign binding gets -- an extra entry that takes an argument holding an arbitrary numeric -- value (an extra data constructor in Haskell), and this value is used -- whenever an unknown value is seen. -- -- When this is Nothing, the enum will not support unknown -- values. toCppEnum in the -- Foreign.Hoppy.Runtime.CppEnum typeclass, as well as calls or -- returns from C++ that pass a value not defined in the interface, will -- raise an error. -- -- Enums that have this set to Nothing should also have -- enumHasBitOperations set to false, to avoid potential errors at -- runtime; see that function's documentation. -- -- The enumValuePrefix applies to this name, just as it does to -- other enum entries. enumUnknownValueEntry :: CppEnum -> Maybe EnumEntryWords -- | Sets the entry name (a list of words, a la the fields in -- EnumValueMap) for the fallback enum entry that holds unknown -- values. -- -- Set enumUnknownValueEntry, enumSetNoUnknownValueEntry. enumSetUnknownValueEntry :: IsEnumUnknownValueEntry a => a -> CppEnum -> CppEnum -- | Sets an enum to have no unknown value entry. -- -- Set enumUnknownValueEntry, enumSetUnknownValueEntry. enumSetNoUnknownValueEntry :: CppEnum -> CppEnum -- | The default value for enumUnknownValueEntry. This is -- ["Unknown"]. enumUnknownValueEntryDefault :: EnumEntryWords -- | Whether generated bindings should support bitwise operations on the -- enum. This defaults to true. -- -- It is not recommended to disable the unknown value entry -- (enumUnknownValueEntry) while having this be true, because any -- computation involving enum values not explicitly defined will cause a -- runtime error. This includes undefined combinations of defined values. enumHasBitOperations :: CppEnum -> Bool -- | Sets whether generated bindings will support bitwise operations on the -- enum. -- -- See enumHasBitOperations. enumSetHasBitOperations :: Bool -> CppEnum -> CppEnum -- | Reads evaluated data for the named enum from the C++ generator -- environment. cppGetEvaluatedEnumData :: HasCallStack => ExtName -> Generator EvaluatedEnumData -- | Reads evaluated data for the named enum from the Haskell generator -- environment. hsGetEvaluatedEnumData :: HasCallStack => ExtName -> Generator EvaluatedEnumData -- | Returns the Haskell name for an enum. -- -- TODO Clarify, and split into type and data ctor names. 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. toHsEnumCtorName :: CppEnum -> EnumEntryWords -> Generator String -- | Pure version of toHsEnumCtorName that doesn't create a -- qualified name. toHsEnumCtorName' :: CppEnum -> EnumEntryWords -> String instance Foreign.Hoppy.Generator.Spec.Enum.IsEnumUnknownValueEntry Foreign.Hoppy.Generator.Spec.Base.EnumEntryWords instance Foreign.Hoppy.Generator.Spec.Enum.IsEnumUnknownValueEntry GHC.Base.String instance Foreign.Hoppy.Generator.Spec.Enum.IsAutoEnumValue (Foreign.Hoppy.Generator.Spec.Base.EnumEntryWords, GHC.Base.String) instance Foreign.Hoppy.Generator.Spec.Enum.IsAutoEnumValue GHC.Base.String instance GHC.Classes.Eq Foreign.Hoppy.Generator.Spec.Enum.CppEnum instance GHC.Show.Show Foreign.Hoppy.Generator.Spec.Enum.CppEnum instance Foreign.Hoppy.Generator.Spec.Base.Exportable Foreign.Hoppy.Generator.Spec.Enum.CppEnum instance Foreign.Hoppy.Generator.Spec.Base.HasExtNames Foreign.Hoppy.Generator.Spec.Enum.CppEnum instance Foreign.Hoppy.Generator.Spec.Base.HasReqs Foreign.Hoppy.Generator.Spec.Enum.CppEnum instance Foreign.Hoppy.Generator.Spec.Base.HasAddendum Foreign.Hoppy.Generator.Spec.Enum.CppEnum -- | 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 -- | Indicates strings that are error messages. type ErrorMsg = String -- | 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 -- | Optional parameters when constructing an Interface with -- interface. newtype 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 :: HasCallStack => 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 -- | The C++ compiler for the generator itself to use when building -- temporary code for the interface. This can be overridden or disabled. -- This defaults to defaultCompiler. -- -- This is separate from the ./configure && make -- compilation process used by -- Foreign.Hoppy.Runtime.Setup.cppMain to build generated C++ -- bindings (see hoppy-runtime). This compiler is used to evaluate enums' -- numeric values when the generator is called, and is not used -- otherwise. See makeAutoEnum and -- Foreign.Hoppy.Generator.Hooks. interfaceCompiler :: Interface -> Maybe SomeCompiler -- | Replaces the default compiler used by the interface. -- --
--   interfaceSetCompiler c = interfaceSetCompiler' (SomeCompiler c)
--   
interfaceSetCompiler :: Compiler a => a -> Interface -> Interface -- | Replaces the default compiler used by the interface. When given -- Nothing, the interface will not be allowed to compile any -- code when it generates bindings. interfaceSetCompiler' :: Maybe SomeCompiler -> Interface -> Interface -- | Sets an interface to never compile C++ code during binding generation. -- -- This sets the interface to have no compiler, and also asks the -- interface not to do things that require a compiler, which would -- otherwise cause a runtime failure: currently just validation of -- provided enum numeric types (interfaceSetValidateEnumTypes -- False). interfaceSetNoCompiler :: Interface -> Interface -- | Whether to validate manually-provided enum numeric types -- (enumNumericType) using a compiled C++ sizeof(), as is -- done for enums that don't have an enumNumericType set. -- -- This defaults to true, but can be set to false to discourage requiring -- a compiler. See interfaceSetNoCompiler. interfaceValidateEnumTypes :: Interface -> Bool -- | Controls whether the interface will validate manually specified enum -- types (enumNumericType) by compiling a C++ program. -- -- See interfaceValidateEnumTypes. interfaceSetValidateEnumTypes :: Bool -> Interface -> Interface -- | Hooks allowing the interface to execute code at various points during -- the code generator's execution. This defaults to defaultHooks. interfaceHooks :: Interface -> Hooks -- | Modifies the hooks associated with an interface. interfaceModifyHooks :: (Hooks -> Hooks) -> Interface -> Interface -- | An #include directive in a C++ file. data Include -- | Creates an #include <...> directive. -- -- This can be added to most types of C++ entities with -- addReqIncludes. includeStd :: String -> Include -- | Creates an #include "..." directive. -- -- This can be added to most types of C++ entities with -- addReqIncludes. 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' :: HasCallStack => 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 :: HasCallStack => String -> ExtName -- | Generates an ExtName from an Identifier, if the given -- name is absent. extNameOrIdentifier :: HasCallStack => Identifier -> Maybe ExtName -> ExtName -- | Generates an ExtName from an FnName -- Identifier, if the given name is absent. extNameOrFnIdentifier :: HasCallStack => FnName Identifier -> Maybe ExtName -> ExtName -- | Generates an ExtName from a string, if the given name is -- absent. extNameOrString :: String -> Maybe ExtName -> 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 :: HasCallStack => 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 :: HasCallStack => Operator -> OperatorType -- | A path to some C++ object, including namespaces. An identifier -- consists of multiple parts separated by "::". Each part has a -- name string followed by an optional template argument list, where each -- argument gets rendered from a Type (non-type arguments for -- template metaprogramming are not supported). -- -- The Monoid instance inserts a :: between joined -- identifiers. Usually an identifier needs to contain at least one part, -- so mempty is an invalid argument to many functions in Hoppy, -- but it is useful as a base case for appending. data Identifier -- | Creates an identifier from a collection of IdParts, with -- ::s between. makeIdentifier :: [IdPart] -> Identifier -- | The separate parts of the identifier, between ::s. identifierParts :: Identifier -> [IdPart] -- | A single component of an Identifier, between ::s. data IdPart -- | Creates an object representing one component of an identifier. makeIdPart :: String -> Maybe [Type] -> IdPart -- | The name within the enclosing scope. idPartBase :: IdPart -> String -- | Template arguments, if present. idPartArgs :: IdPart -> Maybe [Type] -- | Creates a identifier of the form a, without any namespace -- operators (::). 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 -- | Instances of this typeclass are C++ entities that Hoppy can expose to -- foreign languages: functions, classes, global variables, etc. -- Interfaces are largely composed of exports (grouped into -- modules). Hoppy uses this interface to perform code generation for -- each entity. class (HasAddendum a, HasExtNames a, HasReqs a, Typeable a, Show a) => Exportable a -- | Wraps an exportable object in an existential data type. -- -- The default instance is just toExport = Export, which -- does not need to be overridden in general. toExport :: Exportable a => a -> Export -- | Attempts to cast an exportable object to a specific type, pulling off -- Export wrappers as necessary. -- -- The default castExport = cast is fine. castExport :: (Exportable a, Typeable a, Exportable b, Typeable b) => a -> Maybe b -- | Generates the C++ side of the binding for an entity. -- -- For an entity, Hoppy invokes this function once with SayHeader -- when generating the header file for a module, and once with -- SaySource when generating the corresponding source file. sayExportCpp :: Exportable a => SayExportMode -> a -> Generator () -- | Generates the Haskell side of the binding for an entity. -- -- For an entity, Hoppy invokes this function once with -- SayExportForeignImports when it is time to emit foreign -- imports, and once with SayExportDecls when it is time to -- generate Haskell binding code later in the module. Hoppy may also call -- the function with SayExportBoot, if necessary. -- -- See SayExportMode. sayExportHaskell :: Exportable a => SayExportMode -> a -> Generator () -- | If the export is backed by an C++ enum, then this returns known -- structural information about the enum. This provides information to -- the "evaluate enums" hook so that Hoppy can determine enum values on -- its own. -- -- By default, this returns Nothing. -- -- See Hooks. getExportEnumInfo :: Exportable a => a -> Maybe EnumInfo -- | If the export is backed by a C++ class that is marked as supporting -- exceptions, then this returns the class definition. -- -- By default, this returns Nothing. getExportExceptionClass :: Exportable a => a -> Maybe Class -- | Specifies some C++ object (function or class) to give access to. data Export Export :: a -> Export -- | 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_TPtr :: Type -> Type Internal_TRef :: Type -> Type Internal_TFn :: [Parameter] -> Type -> Type Internal_TObj :: Class -> Type Internal_TObjToHeap :: Class -> Type Internal_TToGc :: Type -> Type Internal_TManual :: ConversionSpec -> 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 -- | Strips a leading Internal_TToGc off of a type. stripToGc :: Type -> Type -- | Indicates whether an entity is scoped or unscoped. -- -- This is used to distinguish unscoped enums (enum) or scoped -- ones (enum class or enum struct). data Scoped -- | Indicates an unscoped entity (e.g. an enum). Unscoped :: Scoped -- | Indicates a scoped entity (e.g. an enum). Scoped :: Scoped -- | Returns true if a Scoped value is scoped, and false if it is -- unscoped. isScoped :: Scoped -> Bool -- | Whether or not const is applied to an entity. data Constness Nonconst :: Constness Const :: Constness -- | Returns the opposite constness value. constNegate :: Constness -> Constness -- | 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 parameter to a function, including a type and an optional name. A -- name can be conveniently associated with a type with the -- (~:) operator. -- -- Two Parameters are equal if their types are equal. data Parameter -- | The parameter's data type. parameterType :: Parameter -> Type -- | Maps a function over a parameter's type. onParameterType :: (Type -> Type) -> Parameter -> Parameter -- | An optional variable name to describe the parameter. This name should -- follow the same rules as ExtName for its contents. parameterName :: Parameter -> Maybe String -- | Objects that can be coerced to function parameter definitions. class Show a => IsParameter a toParameter :: IsParameter a => a -> Parameter -- | Converts a list of parameter-like objects to parameters. toParameters :: IsParameter a => [a] -> [Parameter] -- | An empty parameter list. This should be used instead of a literal -- [] when declaring an empty parameter list, because in the -- context of IsParameter a => [a], the empty list is -- ambiguously typed, even though it doesn't matter which instance is -- selected. np :: [Parameter] -- | Associates a name string with a type to create a Parameter that -- can be given as a function or method parameter, instead of a raw -- Type. The name given here will be included as documentation in -- the generated code. -- -- An empty string given for the name means not to associate a name with -- the parameter. This is useful to leave some parameters unnamed in a -- parameter list while naming other parameters, since the list must -- either contain all Types or all Parameters. (~:) :: IsParameter a => String -> a -> Parameter infixr 0 ~: -- | Defines the process for converting a value in one direction between -- C++ and a foreign language. The type parameter varies depending on the -- actual conversion being defined. data ConversionMethod c -- | The conversion is unsupported. If part of an interface depends on -- performing this conversion, code generation will fail. ConversionUnsupported :: ConversionMethod c -- | The input value and its corresponding output have the same binary -- representation in memory, and require no explicit conversion. Numeric -- types may use this conversion method. BinaryCompatible :: ConversionMethod c -- | Conversion requires a custom process as specified by the argument. -- -- TODO Split into pure (let) vs nonpure (<-)? CustomConversion :: c -> ConversionMethod c -- | The root data type for specifying how conversions happen between C++ -- and foreign values. -- -- The Cpp component of this data structure specifies a C++ -- type, and conversions between it and something that can be marshalled -- over a C FFI layer, if such a conversion is possible in each -- direction. -- -- Each foreign language has its own component that must be specified in -- order for types using this specification to be usable in that -- language. data ConversionSpec -- | Creates a ConversionSpec from an identifying name and a -- specification of the C++ conversion behaviour. By default, no foreign -- language conversion behaviour is configured. For Haskell, this should -- be done by using makeConversionSpecHaskell to specify -- behaviour, then writing that to the conversionSpecHaskell field -- of the ConversionSpec returned here. makeConversionSpec :: String -> ConversionSpecCpp -> ConversionSpec -- | For a ConversionSpec, defines the C++ type and conversions to -- and from a C FFI layer. -- -- Prefer makeConversionSpecCpp to using this data constructor -- directly. -- -- conversionSpecCppName specifies the C++ type of the conversion. -- This will be the type that is passed over the C FFI as well, unless -- conversionSpecCppConversionType overrides it. -- conversionSpecCppConversionToCppExpr and -- conversionSpecCppConversionFromCppExpr may define custom code -- generation for passing values over the FFI. data ConversionSpecCpp ConversionSpecCpp :: String -> Generator Reqs -> Generator (Maybe Type) -> Maybe (Generator () -> Maybe (Generator ()) -> Generator ()) -> Maybe (Generator () -> Maybe (Generator ()) -> Generator ()) -> ConversionSpecCpp -- | The name of the C++ type. May identify a primitive C++ type such as -- "unsigned int", or a more complex type like -- std::list<std::string>. [conversionSpecCppName] :: ConversionSpecCpp -> String -- | Computes requirements to refer to the C++ type. Being in the generator -- monad, this may use its environment, but should not emit code or -- Reqs to the generator directly. [conversionSpecCppReqs] :: ConversionSpecCpp -> Generator Reqs -- | Specifies the type that will be passed over the C FFI. -- -- If absent (default), then the type named by -- conversionSpecCppName is also used for marshalling to foreign -- languages. -- -- If present, this represents a type distinct from -- conversionSpecCppName that will be exchanged across the FFI -- boundary. In this case, you may also want to define one or both of -- conversionSpecCppConversionToCppExpr and -- conversionSpecCppConversionFromCppExpr. -- -- This is a monadic value so that it has access to the generator's -- environment. The action should not add imports or emit code. [conversionSpecCppConversionType] :: ConversionSpecCpp -> Generator (Maybe Type) -- | This controls behaviour for receiving a value passed into C++ over the -- FFI. Specifically, this powers the ConversionSpec being used -- as Function arguments and Callback return values. -- -- When absent (default), generated code assumes that it can implicitly -- convert a value passed over the FFI from the C FFI type (see -- conversionSpecCppConversionType) to the C++ type (i.e. -- conversionSpecCppName). When the former is absent, this is -- always fine. -- -- When present, this provides custom conversion behaviour for receiving -- a value passed into C++ over the FFI. The function should generate C++ -- code to convert a value from the type passed over the C FFI into the -- actual C++ type. -- -- This is a function of the form: -- --
--   \emitFromExpr maybeEmitToVar -> ...
--   
-- -- If the function's second argument is present, then the function should -- emit a variable declaration for that name, created from the expression -- emitted by the first argument. -- -- If the function's second argument is absent, then the function should -- emit an expression that converts the expression emitted by the first -- argument into the appropriate type. -- -- In both cases, the first generator argument should only be evaluated -- once by the resulting C++ expression; it is not guaranteed to be pure. [conversionSpecCppConversionToCppExpr] :: ConversionSpecCpp -> Maybe (Generator () -> Maybe (Generator ()) -> Generator ()) -- | This is the opposite of conversionSpecCppConversionToCppExpr. -- This being present enables custom conversion behaviour for passing a -- value out of C++ through the FFI. This powers the -- ConversionSpec being used as Function return values -- and Callback arguments. [conversionSpecCppConversionFromCppExpr] :: ConversionSpecCpp -> Maybe (Generator () -> Maybe (Generator ()) -> Generator ()) -- | Builds a ConversionSpecCpp with a C++ type, with no conversions -- defined. makeConversionSpecCpp :: String -> Generator Reqs -> ConversionSpecCpp -- | Controls how conversions between C++ values and Haskell values happen -- in Haskell bindings. -- -- Prefer makeConversionSpecHaskell to using this data constructor -- directly. data ConversionSpecHaskell ConversionSpecHaskell :: Generator HsType -> Maybe (HsName -> Generator HsQualType) -> Maybe (Generator HsType) -> ConversionMethod (Generator ()) -> ConversionMethod (Generator ()) -> ConversionSpecHaskell -- | The type exposed to users of the Haskell side of a binding. Functions -- that take one of these values as an argument will expect this type, -- and functions returning one of these values will return this type. -- -- This type is wrapped in a generator in order to be able to specify any -- necessary imports. This generator should not generate code or add -- exports. [conversionSpecHaskellHsType] :: ConversionSpecHaskell -> Generator HsType -- | If present, then for bindings for C++ functions that expect one of -- these values as an argument, rather than taking a fixed concrete type -- (conversionSpecHaskellHsType), this qualified type will be used -- instead. The HsName parameter receives a unique name from the -- generator that can be used with HsTyVar like so: -- --
--   \name -> return $ HsQualType [...constraints...] (HsTyVar name)
--   
-- -- conversionSpecHaskellHsType should satisfy this constraint, -- when present. -- -- This type is wrapped in a generator in order to be able to specify any -- necessary imports. This generator should not generate code or add -- exports. [conversionSpecHaskellHsArgType] :: ConversionSpecHaskell -> Maybe (HsName -> Generator HsQualType) -- | If present, then rather than passing a value of native Haskell type -- (conversionSpecHaskellHsType) directly over the FFI, this is an -- intermediate type that will be passed instead. This is needed any time -- that the former type isn't a simple type that the FFI supports. -- -- conversionSpecHaskellToCppFn and -- conversionSpecHaskellFromCppFn marshal values into and out of -- this type, respsectively. -- -- This type is wrapped in a generator in order to be able to specify any -- necessary imports. This generator should not generate code or add -- exports. [conversionSpecHaskellCType] :: ConversionSpecHaskell -> Maybe (Generator HsType) -- | This defines how a Haskell value is passed to C++. If this is -- CustomConversion, then conversionSpecHaskellCType must -- be present, and the generator should output a function that takes a -- value of type conversionSpecHaskellHsType and return a value of -- conversionSpecHaskellCType. -- -- If conversionSpecHaskellHsArgType is present, then the function -- should be able to accept that more general type instead. This is used -- for bindings that call into C++ functions. This function is still -- specialized to conversionSpecHaskellHsType when generating code -- for callback return values. -- -- The generator should output code and may add imports, but should not -- add exports. [conversionSpecHaskellToCppFn] :: ConversionSpecHaskell -> ConversionMethod (Generator ()) -- | This defines how a Haskell value is passed from C++. If this is -- CustomConversion, then conversionSpecHaskellCType must -- be present, and the generator should output a function that takes a -- value of type conversionSpecHaskellCType and return a value of -- conversionSpecHaskellHsType. -- -- The generator should output code and may add imports, but should not -- add exports. [conversionSpecHaskellFromCppFn] :: ConversionSpecHaskell -> ConversionMethod (Generator ()) -- | Builds a ConversionSpecHaskell with the mandatory parameters -- given. makeConversionSpecHaskell :: Generator HsType -> Maybe (Generator HsType) -> ConversionMethod (Generator ()) -> ConversionMethod (Generator ()) -> ConversionSpecHaskell -- | 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. newtype 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 -- | Modifies an object's exception handlers with a given function. modifyExceptionHandlers :: HandlesExceptions a => (ExceptionHandlers -> ExceptionHandlers) -> a -> a -- | 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). newtype 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 -- | Structural information about a C++ enum. This is used when Hoppy is -- evaluating enum data, see getExportEnumInfo. -- -- See CppEnum. data EnumInfo EnumInfo :: ExtName -> Identifier -> Maybe Type -> Reqs -> Scoped -> EnumValueMap -> EnumInfo -- | The external name of the enum. [enumInfoExtName] :: EnumInfo -> ExtName -- | The enum's identifier. [enumInfoIdentifier] :: EnumInfo -> Identifier -- | The enum's numeric type, if explicitly known to the bindings. This -- does not need to be provided. If absent, then Hoppy will calculate the -- enum's numeric type on its own, using a C++ compiler. If this is -- present however, Hoppy will use it, and additionally validate it -- against what the C++ compiler thinks, if validation is enabled (see -- interfaceValidateEnumTypes). [enumInfoNumericType] :: EnumInfo -> Maybe Type -- | Requirements for accessing the enum. [enumInfoReqs] :: EnumInfo -> Reqs -- | Whether the enum is scoped or unscoped. [enumInfoScoped] :: EnumInfo -> Scoped -- | The entries in the enum. [enumInfoValues] :: EnumInfo -> EnumValueMap -- | A list of words that comprise the name of an enum entry. Each string -- in this list is treated as a distinct word for the purpose of -- performing case conversion to create identifiers in foreign languages. -- These values are most easily created from a C++ identifier using -- splitIntoWords. type EnumEntryWords = [String] -- | Describes the entries in a C++ enum. -- -- Equality is defined as having the same enumValueMapValues. data EnumValueMap EnumValueMap :: [EnumEntryWords] -> MapWithForeignLanguageOverrides EnumEntryWords EnumEntryWords -> Map EnumEntryWords EnumValue -> EnumValueMap -- | The names of all entries in the enum being generated, in the order -- specified by the enum definition. These are the strings used to name -- generated bindings. Each name is broken up into words. How the words -- and get combined to make a name in a particular foreign language -- depends on the language. [enumValueMapNames] :: EnumValueMap -> [EnumEntryWords] -- | Per-language renames of enum value entries. [enumValueMapForeignNames] :: EnumValueMap -> MapWithForeignLanguageOverrides EnumEntryWords EnumEntryWords -- | A map specifying for each entry in enumValueMapNames, how to -- determine the entry's numeric value. [enumValueMapValues] :: EnumValueMap -> Map EnumEntryWords EnumValue -- | Describes the value of an entry in a C++ enum. A numeric value may -- either be provided manually, or if omitted, Hoppy can determine it -- automatically. data EnumValue -- | A manually specified numeric enum value. EnumValueManual :: Integer -> EnumValue -- | A numeric enum value that will be determined when the generator is -- run, by means of compiling a C++ program. EnumValueAuto :: Identifier -> EnumValue -- | Languages that Hoppy supports binding to. Currently this is only -- Haskell. data ForeignLanguage -- | The Haskell language. Haskell :: ForeignLanguage -- | A value that may be overridden based on a ForeignLanguage. type WithForeignLanguageOverrides = WithOverrides ForeignLanguage -- | A map whose values may be overridden based on a -- ForeignLanguage. type MapWithForeignLanguageOverrides = MapWithOverrides ForeignLanguage -- | 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) -- | 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 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 copy objects to the heap when being passed out of C++. -- Lifetimes of the resulting objects must be managed by code in the -- foreign language. -- -- Calling this on a class makes objT behave like -- objToHeapT for values being passed out of C++. classSetConversionToHeap :: Class -> Class -- | Modifies a class's ClassConversion structure by setting all -- languages that support garbage collection to copy objects to the heap -- when being passed out of C++, and put those objects under the care of -- the foreign language's garbage collector. -- -- Calling this on a class makes objT behave like toGcT for -- values being passed out of C++. classSetConversionToGc :: Class -> Class -- | 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 -- | Hooks for controlling various parts of generators. module Foreign.Hoppy.Generator.Hook -- | These hooks can be used to customize the behaviour of a Hoppy -- generator. data Hooks Hooks :: EnumEvaluator -> Hooks -- | This hook is invoked once for an interface when the generator needs -- information about some enums beyond what's been baked into the -- interface (for example, to compute the enum's numeric type or entry -- values, see EvaluatedEnumData). This will be called at most -- once per interface per invocation of the generator. [hookEvaluateEnums] :: Hooks -> EnumEvaluator -- | The default set of hooks associated with an interface. This sets -- hookEvaluateEnums to evaluateEnumsWithDefaultCompiler. defaultHooks :: Hooks -- | A function that answers with representation information about an enum -- (e.g. entries' numeric values) for a given request. On success, it -- returns the requested data. On failure, it prints a message to -- standard error and returns Nothing. type EnumEvaluator = EnumEvaluatorArgs -> IO (Maybe EnumEvaluatorResult) -- | Inputs to the process of automatically evaluting enums. data EnumEvaluatorArgs EnumEvaluatorArgs :: Interface -> [FilePath] -> Reqs -> [Identifier] -> [EnumEvaluatorEntry] -> Bool -> EnumEvaluatorArgs -- | The interface that enum values are being calculated for. [enumEvaluatorArgsInterface] :: EnumEvaluatorArgs -> Interface -- | Additional paths to prepend to the C++ include path during -- compilation. [enumEvaluatorArgsPrependedIncludeDirs] :: EnumEvaluatorArgs -> [FilePath] -- | Requirements (includes, etc.) needed to reference the enum identifiers -- being evaluated. [enumEvaluatorArgsReqs] :: EnumEvaluatorArgs -> Reqs -- | The list of identifiers that we need to compute sizeof() for. [enumEvaluatorArgsSizeofIdentifiers] :: EnumEvaluatorArgs -> [Identifier] -- | The list of entries to calculate values for. [enumEvaluatorArgsEntries] :: EnumEvaluatorArgs -> [EnumEvaluatorEntry] -- | Whether to leave temporary build inputs and outputs on disk in case -- the calculation fails. If failure does occur and this is true, then -- the calculation should print to standard error the location of these -- files (this is taken care of by the calculateEnumValues* -- functions here.) [enumEvaluatorArgsKeepOutputsOnFailure] :: EnumEvaluatorArgs -> Bool -- | An entry in an enumeration. This also tracks whether the entry came -- from a scoped enum, for assertion reasons. data EnumEvaluatorEntry EnumEvaluatorEntry :: Scoped -> Identifier -> EnumEvaluatorEntry -- | Whether the entry comes from a scoped enum. [enumEvaluatorEntryScoped] :: EnumEvaluatorEntry -> Scoped -- | The identifier referring to the entry. [enumEvaluatorEntryIdentifier] :: EnumEvaluatorEntry -> Identifier -- | Raw outputs parsed from the output of an enum evaluator. data EnumEvaluatorResult EnumEvaluatorResult :: ![Int] -> ![Integer] -> EnumEvaluatorResult -- | The sizeof() for each identifier in -- enumEvaluatorArgsSizeofIdentifiers. The lengths of these two -- lists must match. [enumEvaluatorResultSizes] :: EnumEvaluatorResult -> ![Int] -- | The numeric value for each identifier in -- enumEvaluatorArgsEntries. The lengths of these two lists must -- match. [enumEvaluatorResultValues] :: EnumEvaluatorResult -> ![Integer] -- | Evaluate enums using a specified compiler. evaluateEnumsWithCompiler :: Compiler a => a -> EnumEvaluator -- | Calculates enum values using an interface's compiler. evaluateEnumsWithDefaultCompiler :: EnumEvaluator -- | Constructs the C++ source program to evaluate enums. makeCppSourceToEvaluateEnums :: EnumEvaluatorArgs -> ByteString -- | Interprets the output of a program generated by -- makeCppSourceToEvaluateEnums, returning parsed values if -- successful, and an error string otherwise. interpretOutputToEvaluateEnums :: EnumEvaluatorArgs -> String -> Either String EnumEvaluatorResult -- | Bound information about numeric types. data NumericTypeInfo -- | Selects the preferred numeric type for holding numeric values in the -- given range. pickNumericType :: Int -> Integer -> Integer -> Maybe NumericTypeInfo -- | Collects all of the enum values that need calculating in an interface, -- runs the hook to evaluate them, and stores the result in the -- interface. This won't recalculate enum data if it's already been -- calculated. internalEvaluateEnumsForInterface :: Interface -> Maybe FilePath -> Bool -> IO (Map ExtName EvaluatedEnumData) instance GHC.Classes.Eq Foreign.Hoppy.Generator.Hook.EnumEvaluatorEntry instance GHC.Show.Show Foreign.Hoppy.Generator.Hook.EnumEvaluatorResult instance GHC.Show.Show Foreign.Hoppy.Generator.Hook.OrdIdentifier instance GHC.Classes.Eq Foreign.Hoppy.Generator.Hook.OrdIdentifier instance GHC.Classes.Ord Foreign.Hoppy.Generator.Hook.EnumEvaluatorEntry instance GHC.Classes.Ord Foreign.Hoppy.Generator.Hook.OrdIdentifier -- | 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 -- | Removes the generated files in C++ bindings. CleanCpp :: FilePath -> Action -- | Removes the generated files in Haskell bindings. CleanHs :: FilePath -> Action -- | Instructs the generator to keep on disk any temporary programs or -- files created, in case of failure. KeepTempOutputsOnFailure :: Action -- | Dumps to stdout information about all external names in the current -- interface. DumpExtNames :: Action -- | Dumps to stdout information about all enums in the current interface. DumpEnums :: Action -- | Specifies the path to a enum evaluation cache file to use. EnumEvalCachePath :: Maybe FilePath -> Action -- | Specifies the behaviour with respect to how the enum evaluation cache -- cache file is used. EnumEvalCacheMode :: EnumEvalCacheMode -> Action -- | Controls the behaviour of a generatior with respect to the enum cache -- file, when a file path provided (--enum-eval-cache-path). -- -- If enum evaluation is required, based on the presence of the cache -- file and which of these modes is selected, then the compiler will be -- called and the results will be written to the cache file -- -- If an enum cache file path is not provided, then this mode is ignored, -- and enum evaluation is attempted if a generator requires it. -- -- Change detection is not currently supported. There is no ability to -- detect whether the cache file is up to date and contains all of the -- enum entries for the current state of the enums defined in an -- interface. The cache file is meant to be refreshed with -- RefreshEnumCache when building the C++ binding package, and -- installed with them so that the Haskell binding package can use -- EnumCacheMustExist. data EnumEvalCacheMode -- | The default. Ignore the presence of an existing cache file, and -- evaluate enums freshly, updating the cache file with new contents. RefreshEnumCache :: EnumEvalCacheMode -- | Require the cache file to exist. If it does not, enum evaluation will -- not be attempted; the generator will exit unsuccessfully instead. EnumCacheMustExist :: EnumEvalCacheMode -- | 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 () -- | Ensures that all of the entries in a list of results coming from -- interface are successful, and returns the list of -- Interface values. If any results are unsuccessful, then an -- error message is printed, and the program exits with an error -- (exitFailure). ensureInterfaces :: [Either String Interface] -> IO [Interface] -- | 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. -- -- Arguments are processed in the order given, this means that settings -- must come before action arguments. -- -- run :: [Interface] -> [String] -> IO [Action]