hoppy-generator-0.8.0: C++ FFI generator - Code generator
Safe HaskellNone
LanguageHaskell2010

Foreign.Hoppy.Generator.Language.Haskell

Description

Shared portion of the Haskell code generator. Usable by binding definitions.

Synopsis

Documentation

data Managed Source #

Indicates who is managing the lifetime of an object via an object pointer.

Constructors

Unmanaged

The object's lifetime is being managed manually.

Managed

The object's lifetime is being managed by the Haskell garbage collector.

getModuleName :: Interface -> Module -> String Source #

Returns the complete Haskell module name for a Module in an Interface, taking into account the interfaceHaskellModuleBase and the moduleHaskellName.

toModuleName :: String -> String Source #

Performs case conversions on the given string to ensure that it is a valid component of a Haskell module name.

Code generators

data Partial Source #

A partially-rendered Module. Contains all of the module's bindings, but may be subject to further processing.

Constructors

Partial 

Fields

Instances

Instances details
Eq Partial Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Language.Haskell

Methods

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

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

Ord Partial Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Language.Haskell

data Output Source #

A chunk of generated Haskell code, including information about imports and exports.

Constructors

Output 

Fields

  • outputExports :: [HsExport]

    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.

  • outputImports :: HsImportSet

    Haskell module imports. Should include all imports needed for the outputBody.

  • outputBody :: [String]

    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.

  • outputExtensions :: Set String

    Language extensions to enable via the {--} pragma for the whole module.

Instances

Instances details
Semigroup Output Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Language.Haskell

Monoid Output Source # 
Instance details

Defined in Foreign.Hoppy.Generator.Language.Haskell

type Generator = ReaderT Env (WriterT Output (Except ErrorMsg)) Source #

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.

runGenerator :: Interface -> ComputedInterfaceData -> Module -> Generator a -> Either ErrorMsg (Partial, a) Source #

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.

evalGenerator :: Interface -> ComputedInterfaceData -> Module -> Generator a -> Either ErrorMsg a Source #

Runs a generator action and returns the its value.

execGenerator :: Interface -> ComputedInterfaceData -> Module -> Generator a -> Either ErrorMsg Partial Source #

Runs a generator action and returns its output.

renderPartial :: Partial -> String Source #

Converts a Partial into a complete Haskell module.

data Env Source #

Context information for generating Haskell code.

askInterface :: Generator Interface Source #

Returns the currently generating interface.

askComputedInterfaceData :: Generator ComputedInterfaceData Source #

Returns the computed data for the currently generating interface.

askModule :: Generator Module Source #

Returns the currently generating module.

askModuleName :: Generator String Source #

Returns the currently generating module's Haskell module name.

getModuleForExtName :: ExtName -> Generator Module Source #

Looks up the Module containing a given external name, throwing an error if it can't be found.

withErrorContext :: String -> Generator a -> Generator a Source #

Adds context information to the end of any error message thrown by the action. See Generator.

inFunction :: String -> Generator a -> Generator a Source #

Adds the given function name to any error message thrown by the action, for context.

Exports

type HsExport = String Source #

Indicates strings that represent an item in a Haskell module export list.

addExport :: HsExport -> Generator () Source #

Adds an export to the current module.

addExport' :: HsExport -> Generator () Source #

addExport' "x" adds an export of the form x (..) to the current module.

addExports :: [HsExport] -> Generator () Source #

Adds multiple exports to the current module.

Imports

addImports :: HsImportSet -> Generator () Source #

Adds imports to the current module.

Language extensions

addExtension :: String -> Generator () Source #

Adds a Haskell language extension to the current module.

Code generation

data SayExportMode Source #

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

Constructors

SayExportForeignImports

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.

SayExportDecls

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.

SayExportBoot

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.

sayLn :: String -> Generator () Source #

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.

saysLn :: [String] -> Generator () Source #

Outputs multiple words to form a line of Haskell code (effectively saysLn = sayLn . concat).

ln :: Generator () Source #

Outputs an empty line of Haskell code. This is reportedly valid Perl code as well.

indent :: Generator a -> Generator a Source #

Runs the given action, indenting all code output by the action one level.

indentSpaces :: Int -> Generator a -> Generator a Source #

Runs the given action, indenting all code output by the action N spaces.

sayLet :: [Generator ()] -> Maybe (Generator ()) -> Generator () Source #

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.

getExtNameModule :: ExtName -> Generator Module Source #

Looks up the module that exports an external name. Throws an error if the external name is not exported.

addExtNameModule :: ExtName -> String -> Generator String Source #

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.

toHsTypeName :: Constness -> ExtName -> Generator String Source #

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 -> String Source #

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

toHsFnName :: ExtName -> Generator String Source #

Converts an external name into a name suitable for a Haskell function or variable.

toHsFnName' :: ExtName -> String Source #

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

toArgName :: Int -> String Source #

Returns a distinct argument variable name for each nonnegative number.

data HsTypeSide Source #

The Haskell side of bindings performs conversions between C FFI types and Haskell types. This denotes which side's type is being used.

Constructors

HsCSide

The C type sent from C++.

HsHsSide

The Haskell-native type.

cppTypeToHsTypeAndUse :: HsTypeSide -> Type -> Generator HsType Source #

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.

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.

prettyPrint :: Pretty a => a -> String Source #

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.