-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | C++ FFI generator - Runtime support -- -- Hoppy generates Haskell bindings to C++ libraries. -- -- This package provides common runtime functionality used by generated -- bindings. @package hoppy-runtime @version 0.7.0 -- | Runtime support for generated Haskell bindings. module Foreign.Hoppy.Runtime -- | Converts between integral types by going from a to -- b, and also round-tripping the b value back to an -- a value. If the two a values don't match, then an -- error is signalled. coerceIntegral :: (Integral a, Integral b, Typeable a, Typeable b, Show a) => a -> b -- | An instance e of this class represents a value belonging to a -- C++ enumeration with numeric type n. class CppEnum n e | e -> n -- | Converts a number into an enum value. -- -- If the Hoppy binding didn't request that the enum support arbitrary -- unknown values, then given an entry not explicitly supported by the -- enum, this throws an exception. toCppEnum :: (CppEnum n e, HasCallStack) => n -> e -- | Extracts the number that an enum value represents. fromCppEnum :: CppEnum n e => e -> n -- | An instance of this class represents a handle (a pointer) to a C++ -- object. All C++ classes bound by Hoppy have instances of -- CppPtr. The lifetime of such an object can optionally be -- managed by the Haskell garbage collector. Handles returned from -- constructors are unmanaged, and toGc converts an unmanaged -- handle to a managed one. delete must not be called on managed -- handles. class CppPtr this -- | Polymorphic null pointer handle. nullptr :: CppPtr this => this -- | Runs an IO action on the Ptr underlying this handle. Equivalent -- to withForeignPtr for managed handles: the Ptr is only -- guaranteed to be valid until the action returns. There is no such -- restriction for unmanaged handles, but of course the object must still -- be alive to be used. withCppPtr :: CppPtr this => this -> (Ptr this -> IO a) -> IO a -- | Converts to a regular pointer. For objects managed by the garbage -- collector, this comes with the warnings associated with -- unsafeForeignPtrToPtr, namely that the object may be collected -- immediately after this function returns unless there is a -- touchCppPtr call later on. toPtr :: CppPtr this => this -> Ptr this -- | Equivalent to touchForeignPtr for managed handles. Has no -- effect on unmanaged handles. touchCppPtr :: CppPtr this => this -> IO () -- | C++ values that can be deleted. By default, C++ classes bound by Hoppy -- are assumed to be deletable, so they get instances of -- Deletable. class Deletable this -- | Deletes the object with the C++ delete operator. delete :: Deletable this => this -> IO () -- | Converts a handle to one managed by the garbage collector. A -- new managed handle is returned, and existing handles -- including the argument remain unmanaged, becoming invalid once -- all managed handles are unreachable. Calling this on an already -- managed handle has no effect and the argument is simply returned. It -- is no longer safe to call delete on the given object after -- calling this function. It is also not safe to call this function on -- unmanaged handles for a single object multiple times: the object will -- get deleted more than once. -- -- Up- and downcasting managed handles keeps the object alive correctly. toGc :: Deletable this => this -> IO this -- | A typeclass for references to C++ values that can be assigned to. This -- includes raw pointers (Ptr), as well as handles for object -- types that have an assignment operator (see Assignable). class Assignable cppType value -- | assign x v assigns the value v at the location -- pointed to by x. assign :: Assignable cppType value => cppType -> value -> IO () -- | A typeclass for creating copies of C++ objects. Every C++ class with a -- copy constructor will have two instances: -- --
--   instance Copyable Foo Foo
--   instance Copyable FooConst Foo
--   
class Copyable from to | from -> to copy :: Copyable from to => from -> IO to -- | For a C++ class that also has a native Haskell representation (e.g. -- value types such as std::string), this typeclass allows -- converting a Haskell value into a C++ object on the heap. Encoding to -- both the non-const and const objects is supported. -- -- Because the functional dependency points in the direction it does, -- calls of the form encode value are ambiguously typed, -- so encodeAs is provided to resolve the ambiguity. -- -- Prefer withCppObj over calling encode directly, to -- manage the lifetime of the object. -- -- See also Decodable. class Encodable cppPtrType hsType | cppPtrType -> hsType encode :: Encodable cppPtrType hsType => hsType -> IO cppPtrType -- | Takes a dummy argument to help with type resolution of encode, -- a la asTypeOf. For example, for a handle type -- StdString that gets converted to a regular haskell -- String, the expected usage is: -- --
--   str :: String
--   encodeAs (undefined :: StdString) str
--   
encodeAs :: Encodable cppPtrType hsType => cppPtrType -> hsType -> IO cppPtrType -- | A typeclass for converting references to C++ values into Haskell -- values. What this means depends on the type of C++ value. Pointers to -- numeric types and to other pointers (i.e. Ptr (Ptr -- ...)) are decodable by peeking at the value. -- -- For a C++ class that also has a native Haskell representation (e.g. -- value types such as std::string), this typeclass allows -- converting a C++ heap object into a Haskell value based on the defined -- conversion. Decoding from both the non-const and const objects is -- supported. -- -- See also Encodable. class Decodable cppPtrType hsType | cppPtrType -> hsType decode :: Decodable cppPtrType hsType => cppPtrType -> IO hsType -- | Decodes a C++ object to a Haskell value with decode, releases -- the original object with delete, then returns the Haskell -- value. decodeAndDelete :: (Deletable cppPtrType, Decodable cppPtrType hsType) => cppPtrType -> IO hsType -- | Temporarily encodes the Haskell value into a C++ object and passes it -- to the given function. When the function finishes, the C++ object is -- deleted. withCppObj :: (Deletable cppPtrType, Encodable cppPtrType hsType) => hsType -> (cppPtrType -> IO a) -> IO a -- | withScopedPtr m f runs m to get a handle, which is -- given to f to execute. When f finishes, the handle -- is deleted (via bracket and delete). withScopedPtr :: Deletable cppPtrType => IO cppPtrType -> (cppPtrType -> IO a) -> IO a -- | withScopedFunPtr m f runs m to get a FunPtr, -- which is given to f to execute. When f finishes, the -- FunPtr is deleted (via bracket and -- freeHaskellFunPtr). This is useful in conjunction with function -- pointers created via generated callback functions. withScopedFunPtr :: IO (FunPtr a) -> (FunPtr a -> IO b) -> IO b -- | A typeclass for C++ values that are catchable as exceptions. C++ -- classes that have been declared to be used as exceptions have -- instances of this class. Unlike CppThrowable, -- UnknownCppException is also an instance of this typeclass. class CppException e -- | Internal. Returns metadata about the exception. cppExceptionInfo :: CppException e => e -> ExceptionClassInfo -- | Internal. Constructs a handle from a GC-managed object's raw pointers. cppExceptionBuild :: CppException e => ForeignPtr () -> Ptr () -> e -- | Internal. Constructs a GC-managed handle from an unmanaged raw -- pointer. cppExceptionBuildToGc :: CppException e => Ptr () -> IO e -- | A typeclass for C++ values that are throwable as exceptions. C++ -- classes that have been declared to be used as exceptions have -- instances of this class. class CppException e => CppThrowable e -- | Internal. Creates a throwable exception from a C++ handle. toSomeCppException :: CppThrowable e => e -> SomeCppException -- | Catches a C++ exception, similar to catch. Catching an -- exception class will also catch subtypes of the class, per normal C++ -- exception semantics. Catching UnknownCppException will catch -- all C++ exceptions, but will provide no information about the caught -- exception. Exceptions caught with this function are GC-managed heap -- objects; you do not need to manually delete them. catchCpp :: forall a e. CppException e => IO a -> (e -> IO a) -> IO a -- | Takes ownership of a C++ object, and throws it as a Haskell exception. -- This can be caught in Haskell with catchCpp, or propagated to -- C++ when within a callback that is marked as handling exceptions. throwCpp :: CppThrowable e => e -> IO a -- | A top type for C++ exceptions. Catching this type with catchCpp -- will catch all C++ exceptions. (You still have to declare what -- exceptions can be thrown from each function, to make exceptions pass -- through the gateway properly.) data UnknownCppException -- | Containers whose contents can be convered to a list. -- -- For a container Cont holding values with C-side type -- Foo and Haskell-side type Bar, if the container uses -- ConvertPtr then the following instances are recommended: -- --
--   instance HasContents ContConst FooConst
--   instance HasContents Cont Foo
--   
-- -- If the container uses ConvertValue then the following instances -- are recommended: -- --
--   instance HasContents ContConst Bar
--   instance HasContents Cont Bar
--   
class HasContents c e | c -> e -- | Extracts the contents of a container, returning the elements in a -- list. toContents :: HasContents c e => c -> IO [e] -- | Containers that can be created from a list. -- -- For a container Cont holding values with C-side type -- Foo and Haskell-side type Bar, if the container uses -- ConvertPtr then the following instance is recommended: -- --
--   instance FromContents Cont Foo
--   
-- -- If the container uses ConvertValue then the following instance -- is recommended: -- --
--   instance HasContents Cont Bar
--   
-- -- No instances for ContConst are needed because it is easy -- enough to cast the resulting collection to a const pointer. class FromContents c e | c -> e -- | Creates and returns a new container holding the given elements. fromContents :: FromContents c e => [e] -> IO c -- | Internal type that represents a pointer to a C++ callback object -- (callback impl object, specifically). newtype CCallback fnHsCType CCallback :: Ptr () -> CCallback fnHsCType -- | A global constant function pointer that points to -- freeHaskellFunPtr. freeHaskellFunPtrFunPtr :: FunPtr (FunPtr (IO ()) -> IO ()) -- | A unique identifier for a C++ class. The representation is internal to -- Hoppy. newtype ExceptionId ExceptionId :: CInt -> ExceptionId -- | Internal. Holds an arbitrary CppException. -- -- Do not catch this with catch; this can leak exception objects. -- Always use catchCpp to catch C++ exceptions. data SomeCppException SomeCppException :: ExceptionClassInfo -> Maybe (ForeignPtr ()) -> Ptr () -> SomeCppException SomeUnknownCppException :: SomeCppException -- | Internal. Wraps a call to a C++ gateway function, and provides -- propagation of C++ exceptions to Haskell. internalHandleExceptions :: ExceptionDb -> (Ptr CInt -> Ptr (Ptr ()) -> IO a) -> IO a -- | Internal. Wraps a call to a Haskell function while invoking a -- callback, and provides propagation of C++ exceptions back into C++. internalHandleCallbackExceptions :: CppDefault a => Ptr CInt -> Ptr (Ptr ()) -> IO a -> IO a -- | Internal. A database of information about exceptions an interface -- uses. newtype ExceptionDb ExceptionDb :: Map ExceptionId ExceptionClassInfo -> ExceptionDb -- | Internal. Information about a C++ exception class. data ExceptionClassInfo ExceptionClassInfo :: ExceptionId -> String -> Map ExceptionId (Ptr () -> Ptr ()) -> (Ptr () -> IO ()) -> (Ptr () -> IO (Ptr ())) -> (Ptr () -> IO (ForeignPtr ())) -> ExceptionClassInfo [exceptionClassId] :: ExceptionClassInfo -> ExceptionId [exceptionClassName] :: ExceptionClassInfo -> String -- | This maps ancestor classes' exception IDs to functions that cast -- pointers from the current type to the ancestor type. [exceptionClassUpcasts] :: ExceptionClassInfo -> Map ExceptionId (Ptr () -> Ptr ()) -- | Deletes the object. [exceptionClassDelete] :: ExceptionClassInfo -> Ptr () -> IO () -- | Invokes the object's copy constructor. [exceptionClassCopy] :: ExceptionClassInfo -> Ptr () -> IO (Ptr ()) -- | Assigns the object to the Haskell garbage collector, a la toGc. [exceptionClassToGc] :: ExceptionClassInfo -> Ptr () -> IO (ForeignPtr ()) instance GHC.Show.Show Foreign.Hoppy.Runtime.ExceptionId instance GHC.Classes.Ord Foreign.Hoppy.Runtime.ExceptionId instance GHC.Classes.Eq Foreign.Hoppy.Runtime.ExceptionId instance Foreign.Hoppy.Runtime.CppDefault () instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CBool instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CChar instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CUChar instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CShort instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CUShort instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CInt instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CUInt instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CLong instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CULong instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CLLong instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CULLong instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CFloat instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CDouble instance Foreign.Hoppy.Runtime.CppDefault GHC.Int.Int8 instance Foreign.Hoppy.Runtime.CppDefault GHC.Int.Int16 instance Foreign.Hoppy.Runtime.CppDefault GHC.Int.Int32 instance Foreign.Hoppy.Runtime.CppDefault GHC.Int.Int64 instance Foreign.Hoppy.Runtime.CppDefault GHC.Word.Word8 instance Foreign.Hoppy.Runtime.CppDefault GHC.Word.Word16 instance Foreign.Hoppy.Runtime.CppDefault GHC.Word.Word32 instance Foreign.Hoppy.Runtime.CppDefault GHC.Word.Word64 instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CPtrdiff instance Foreign.Hoppy.Runtime.CppDefault Foreign.C.Types.CSize instance Foreign.Hoppy.Runtime.CppDefault System.Posix.Types.CSsize instance Foreign.Hoppy.Runtime.CppDefault (GHC.Ptr.Ptr a) instance Foreign.Hoppy.Runtime.CppException Foreign.Hoppy.Runtime.UnknownCppException instance GHC.Show.Show Foreign.Hoppy.Runtime.SomeCppException instance GHC.Exception.Type.Exception Foreign.Hoppy.Runtime.SomeCppException instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CBool) GHC.Types.Bool instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CChar) Foreign.C.Types.CChar instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CUChar) Foreign.C.Types.CUChar instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CShort) Foreign.C.Types.CShort instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CUShort) Foreign.C.Types.CUShort instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CInt) GHC.Types.Int instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CUInt) Foreign.C.Types.CUInt instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CLong) Foreign.C.Types.CLong instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CULong) Foreign.C.Types.CULong instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CLLong) Foreign.C.Types.CLLong instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CULLong) Foreign.C.Types.CULLong instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CFloat) GHC.Types.Float instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CDouble) GHC.Types.Double instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr GHC.Int.Int8) GHC.Int.Int8 instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr GHC.Int.Int16) GHC.Int.Int16 instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr GHC.Int.Int32) GHC.Int.Int32 instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr GHC.Int.Int64) GHC.Int.Int64 instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr GHC.Word.Word8) GHC.Word.Word8 instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr GHC.Word.Word16) GHC.Word.Word16 instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr GHC.Word.Word32) GHC.Word.Word32 instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr GHC.Word.Word64) GHC.Word.Word64 instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CPtrdiff) Foreign.C.Types.CPtrdiff instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr Foreign.C.Types.CSize) Foreign.C.Types.CSize instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr System.Posix.Types.CSsize) System.Posix.Types.CSsize instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CBool)) (GHC.Ptr.Ptr Foreign.C.Types.CBool) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CChar)) (GHC.Ptr.Ptr Foreign.C.Types.CChar) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CUChar)) (GHC.Ptr.Ptr Foreign.C.Types.CUChar) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CShort)) (GHC.Ptr.Ptr Foreign.C.Types.CShort) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CUShort)) (GHC.Ptr.Ptr Foreign.C.Types.CUShort) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CInt)) (GHC.Ptr.Ptr Foreign.C.Types.CInt) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CUInt)) (GHC.Ptr.Ptr Foreign.C.Types.CUInt) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CLong)) (GHC.Ptr.Ptr Foreign.C.Types.CLong) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CULong)) (GHC.Ptr.Ptr Foreign.C.Types.CULong) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CLLong)) (GHC.Ptr.Ptr Foreign.C.Types.CLLong) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CULLong)) (GHC.Ptr.Ptr Foreign.C.Types.CULLong) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CFloat)) (GHC.Ptr.Ptr Foreign.C.Types.CFloat) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CDouble)) (GHC.Ptr.Ptr Foreign.C.Types.CDouble) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr GHC.Int.Int8)) (GHC.Ptr.Ptr GHC.Int.Int8) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr GHC.Int.Int16)) (GHC.Ptr.Ptr GHC.Int.Int16) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr GHC.Int.Int32)) (GHC.Ptr.Ptr GHC.Int.Int32) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr GHC.Int.Int64)) (GHC.Ptr.Ptr GHC.Int.Int64) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr GHC.Word.Word8)) (GHC.Ptr.Ptr GHC.Word.Word8) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr GHC.Word.Word16)) (GHC.Ptr.Ptr GHC.Word.Word16) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr GHC.Word.Word32)) (GHC.Ptr.Ptr GHC.Word.Word32) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr GHC.Word.Word64)) (GHC.Ptr.Ptr GHC.Word.Word64) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CPtrdiff)) (GHC.Ptr.Ptr Foreign.C.Types.CPtrdiff) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr Foreign.C.Types.CSize)) (GHC.Ptr.Ptr Foreign.C.Types.CSize) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr System.Posix.Types.CSsize)) (GHC.Ptr.Ptr System.Posix.Types.CSsize) instance Foreign.Hoppy.Runtime.Decodable (GHC.Ptr.Ptr (GHC.Ptr.Ptr (GHC.Ptr.Ptr a))) (GHC.Ptr.Ptr (GHC.Ptr.Ptr a)) instance Foreign.Hoppy.Runtime.Assignable (GHC.Ptr.Ptr Foreign.C.Types.CBool) GHC.Types.Bool instance Foreign.Hoppy.Runtime.Assignable (GHC.Ptr.Ptr Foreign.C.Types.CInt) GHC.Types.Int instance Foreign.Hoppy.Runtime.Assignable (GHC.Ptr.Ptr Foreign.C.Types.CFloat) GHC.Types.Float instance Foreign.Hoppy.Runtime.Assignable (GHC.Ptr.Ptr Foreign.C.Types.CDouble) GHC.Types.Double instance Foreign.Storable.Storable a => Foreign.Hoppy.Runtime.Assignable (GHC.Ptr.Ptr a) a -- | Implementations of Cabal setup programs for use in packages of -- generated bindings. -- -- Much like the default Setup.hs that Cabal recommends for packages, -- --
--   import Distribution.Simple
--   main = defaultMain
--   
-- -- this module provides simplified configuration of packages for -- generated bindings. Suppose you have a project named foobar that is -- composed of Cabal packages named "foobar-generator" for the code -- generator, "foobar-cpp" for the C++ gateway, and "foobar" for the -- Haskell gateway. The C++ gateway package can use the following code: -- --
--   import Foreign.Hoppy.Setup (ProjectConfig (..), cppMain)
--   
--   main =
--     cppMain $
--     ProjectConfig
--     { generatorExecutableName = "foobar-generator"
--     , cppPackageName = "foobar-cpp"
--     , cppSourcesDir = "cpp"
--     , hsSourcesDir = "src"
--     }
--   
-- -- The Haskell gateway uses the same code, except calling hsMain -- instead of cppMain. This causes C++ sources to be generated in -- foobar-cpp/cpp and (assuming the Haskell gateway is at -- foobar/) the Haskell sources to be generated in -- foobar/src. -- -- The gateway packages need to set build-type: Custom in their -- .cabal files to use these setup files. module Foreign.Hoppy.Setup -- | Configuration parameters for a project using Hoppy. data ProjectConfig ProjectConfig :: FilePath -> String -> FilePath -> FilePath -> Maybe String -> ProjectConfig -- | The name of the executable program in the generator package. [generatorExecutableName] :: ProjectConfig -> FilePath -- | The name of the C++ gateway package. [cppPackageName] :: ProjectConfig -> String -- | The directory into which to generate C++ sources, under the C++ -- gateway package root. [cppSourcesDir] :: ProjectConfig -> FilePath -- | The directory into which to generate Haskell sources, under the -- Haskell gateway package root. [hsSourcesDir] :: ProjectConfig -> FilePath -- | If the generator contains multiple interfaces, then this can be used -- to select one. If present, it is passed as an argument to -- --interface when invoking the generator. If absent, the -- default interface is used. [interfaceName] :: ProjectConfig -> Maybe String -- | A main implementation to be used in the Setup.hs of -- a C++ gateway package. -- --
--   cppMain project = defaultMainWithHooks $ cppUserHooks project
--   
cppMain :: ProjectConfig -> IO () -- | Cabal user hooks for a C++ gateway package. When overriding fields in -- the result, be sure to call the previous hook. -- -- The following hooks are defined: -- -- cppUserHooks :: ProjectConfig -> UserHooks -- | A main implementation to be used in the Setup.hs of -- a Haskell gateway package. -- --
--   hsMain project = defaultMainWithHooks $ hsUserHooks project
--   
hsMain :: ProjectConfig -> IO () -- | Cabal user hooks for a Haskell gateway package. When overriding fields -- in the result, be sure to call the previous hook. -- -- The following hooks are defined: -- -- hsUserHooks :: ProjectConfig -> UserHooks