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

Safe HaskellNone
LanguageHaskell2010

Foreign.Hoppy.Generator.Language.Haskell

Contents

Description

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

Synopsis

Documentation

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.

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.

Instances

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 -> String -> 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 -> String -> Generator a -> Either ErrorMsg a Source

Runs a generator action and returns the its value.

execGenerator :: Interface -> String -> 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.

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.

importHsModuleForExtName :: ExtName -> Generator () Source

Imports all of the objects for the given external name into the current module. This is a no-op of the external name is defined in the current module.

Code generation

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.

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.

toHsEnumTypeName :: CppEnum -> String Source

Returns the Haskell name for an enum.

toHsEnumCtorName :: CppEnum -> [String] -> String Source

Constructs the data constructor name for a value in an enum. Like C++ and unlike say Java, Haskell enum values aren't in a separate enum-specific namespace, so we prepend the enum name to the value name to get the data constructor name. The value name is a list of words; see enumValueNames.

toHsBitspaceTypeName :: Bitspace -> String Source

Returns the Haskell name for a bitspace. See toHsEnumTypeName.

toHsBitspaceValueName :: Bitspace -> [String] -> String Source

Constructs the data constructor name for a value in a bitspace. See toHsEnumCtorName.

toHsBitspaceToNumName :: Bitspace -> String Source

Returns the name of the function that will convert a bitspace value into a raw numeric value.

toHsBitspaceClassName :: Bitspace -> String Source

The name of the Haskell typeclass that contains a method for converting to a bitspace value.

toHsBitspaceFromValueName :: Bitspace -> String Source

The name of the method in the toHsBitspaceClassName typeclass that constructs bitspace values.

toHsValueClassName :: Class -> String Source

The name for the typeclass of types that can be represented as values of the given C++ class.

toHsWithValuePtrName :: Class -> String Source

The name of the method within the toHsValueClassName typeclass for accessing an object of the type as a pointer.

toHsPtrClassName :: Constness -> Class -> String Source

The name for the typeclass of types that are (possibly const) pointers to objects of the given C++ class, or subclasses.

toHsCastMethodName :: Constness -> Class -> String Source

The name of the function that upcasts pointers to the specific class type and constness.

toHsDownCastClassName :: Constness -> Class -> String Source

The name of the typeclass that provides a method to downcast to a specific class type. See toHsDownCastMethodName.

toHsDownCastMethodName :: Constness -> Class -> String Source

The name of the function that downcasts pointers to the specific class type and constness.

toHsCastPrimitiveName :: Class -> Class -> String Source

The import name for the foreign function that casts between two specific pointer types. Used for upcasting and downcasting.

toHsConstCastFnName :: Constness -> Class -> String Source

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.

toHsDataTypeName :: Constness -> Class -> String Source

The name of the data type that represents a pointer to an object of the given class and constness.

toHsClassDeleteFnName :: Class -> String Source

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.

toHsMethodName :: Class -> Method -> String Source

Returns the name of the Haskell function that invokes the given method.

See also getClassyExtName.

toHsMethodName' :: IsFnName String name => Class -> name -> String Source

Returns the name of the Haskell function that invokes a method with a specific name in a class.

toHsCallbackCtorName :: Callback -> String Source

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.

toHsFnName :: ExtName -> String Source

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

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.

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.