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

Safe HaskellNone
LanguageHaskell2010

Foreign.Hoppy.Generator.Language.Cpp

Contents

Description

Shared portion of the C++ code generator. Usable by binding definitions.

Synopsis

Code generation monad

type Generator = ReaderT Env (WriterT [Chunk] (Either ErrorMsg)) Source #

A generator monad for C++ code.

TODO This should not simply be a type synonym.

data Env Source #

Context information for generating C++ code.

execGenerator :: Interface -> Module -> Maybe String -> Generator a -> Either ErrorMsg String Source #

Runs a generator action and returns its output, or an error message if unsuccessful.

addIncludes :: MonadWriter [Chunk] m => [Include] -> m () Source #

Adds #include statements to the includes block generated at the top of the currently generating file.

addInclude :: MonadWriter [Chunk] m => Include -> m () Source #

Adds an #include statement to the includes block generated at the top of the currently generating file.

addReqsM :: MonadWriter [Chunk] m => Reqs -> m () Source #

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.

askInterface :: MonadReader Env m => m Interface Source #

Returns the currently generating interface.

askModule :: MonadReader Env m => m Module Source #

Returns the currently generating module.

abort :: ErrorMsg -> Generator a Source #

Halts generation and returns the given error message.

Names

makeCppName :: [String] -> String Source #

Constructs a C++ identifier by combining a list of strings with __.

externalNameToCpp :: ExtName -> String Source #

Returns the C++ binding function name for an external name.

toArgName :: Int -> String Source #

Returns a distinct argument variable name for each nonnegative number.

toArgNameAlt :: Int -> String Source #

Same as toArgName, but with distinct names, with with similarity between toArgName n and toArgNameAlt n.

exceptionIdArgName :: String Source #

The C++ variable name to use for the exception ID argument in a gateway function.

exceptionPtrArgName :: String Source #

The C++ variable name to use for the exception pointer argument in a gateway function.

exceptionVarName :: String Source #

The C++ variable name to use in a catch statement in a gateway function.

exceptionRethrowFnName :: String Source #

The name of the C++ function that receives an exception from a foreign language and throws it in C++.

Token rendering

data Chunk Source #

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.

Constructors

Chunk 

codeChunk :: String -> Chunk Source #

Builds a Chunk that contains the given code string.

includesChunk :: Set Include -> Chunk Source #

Builds a Chunk that contains the given includes.

runChunkWriter :: Writer [Chunk] a -> (a, Chunk) Source #

Runs a Chunk writer, combining them with combineChunks to form a single string.

evalChunkWriter :: Writer [Chunk] a -> a Source #

Runs a Chunk writer and returns the monad's value.

execChunkWriter :: Writer [Chunk] a -> Chunk Source #

Runs a Chunk writer and returns the written log.

runChunkWriterT :: Monad m => WriterT [Chunk] m a -> m (a, Chunk) Source #

Runs a Chunk writer transformer, combining them with combineChunks to form a single string.

evalChunkWriterT :: Monad m => WriterT [Chunk] m a -> m a Source #

Runs a Chunk writer transformer and returns the monad's value.

execChunkWriterT :: Monad m => WriterT [Chunk] m a -> m Chunk Source #

Runs a Chunk writer transformer and returns the written log.

High-level code generation

data SayExportMode Source #

The section of code that Hoppy is generating, for an export.

Constructors

SaySource

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.

SayHeader

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.

say :: MonadWriter [Chunk] m => String -> m () Source #

Emits a single Chunk.

says :: MonadWriter [Chunk] m => [String] -> m () Source #

Emits a Chunk for each string in a list.

renderIdentifier :: Identifier -> String Source #

Renders an Identifier to a string.

sayVar :: MonadWriter [Chunk] m => String -> Maybe [String] -> Type -> m () Source #

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.

sayType :: MonadWriter [Chunk] m => Maybe [String] -> Type -> m () Source #

sayType maybeParamNames t renders t in C++ syntax. If t is a fnT, then maybeParamNames will provide variable names for parameters, if present.

sayFunction Source #

Arguments

:: String

Function name.

-> [String]

Parameter names.

-> Type

Function type. This should use fnT or fnT'.

-> Maybe (Generator ())

If present, then the function is defined and the action here is used to render its body. If absent, then the function is only declared (no function body).

-> Generator () 

Renders a C++ function.

Auxiliary functions

typeToCType :: Type -> Generator (Maybe Type) Source #

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.

typeReqs :: Type -> Generator Reqs Source #

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.

findExportModule :: ExtName -> Generator Module Source #

Looks up the module exporting the given external name in the current interface. abort is called if the external name is not found.

getEffectiveExceptionHandlers :: ExceptionHandlers -> Generator ExceptionHandlers Source #

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.