Safe Haskell | None |
---|---|
Language | Haskell2010 |
Shared portion of the Haskell code generator. Usable by binding definitions.
- data Managed
- getModuleName :: Interface -> Module -> String
- toModuleName :: String -> String
- data Partial = Partial {}
- data Output = Output {
- outputExports :: [HsExport]
- outputImports :: HsImportSet
- outputBody :: [String]
- type Generator = ReaderT Env (WriterT Output (Except ErrorMsg))
- runGenerator :: Interface -> String -> Generator a -> Either ErrorMsg (Partial, a)
- evalGenerator :: Interface -> String -> Generator a -> Either ErrorMsg a
- execGenerator :: Interface -> String -> Generator a -> Either ErrorMsg Partial
- renderPartial :: Partial -> String
- withErrorContext :: String -> Generator a -> Generator a
- inFunction :: String -> Generator a -> Generator a
- type HsExport = String
- addExport :: HsExport -> Generator ()
- addExport' :: HsExport -> Generator ()
- addExports :: [HsExport] -> Generator ()
- addImports :: HsImportSet -> Generator ()
- importHsModuleForExtName :: ExtName -> Generator ()
- sayLn :: String -> Generator ()
- saysLn :: [String] -> Generator ()
- ln :: Generator ()
- indent :: Generator a -> Generator a
- sayLet :: [Generator ()] -> Maybe (Generator ()) -> Generator ()
- toHsEnumTypeName :: CppEnum -> String
- toHsEnumCtorName :: CppEnum -> [String] -> String
- toHsBitspaceTypeName :: Bitspace -> String
- toHsBitspaceValueName :: Bitspace -> [String] -> String
- toHsBitspaceToNumName :: Bitspace -> String
- toHsBitspaceClassName :: Bitspace -> String
- toHsBitspaceFromValueName :: Bitspace -> String
- toHsValueClassName :: Class -> String
- toHsWithValuePtrName :: Class -> String
- toHsPtrClassName :: Constness -> Class -> String
- toHsCastMethodName :: Constness -> Class -> String
- toHsDownCastClassName :: Constness -> Class -> String
- toHsDownCastMethodName :: Constness -> Class -> String
- toHsCastPrimitiveName :: Class -> Class -> String
- toHsConstCastFnName :: Constness -> Class -> String
- toHsDataTypeName :: Constness -> Class -> String
- toHsDataCtorName :: Managed -> Constness -> Class -> String
- toHsClassDeleteFnName :: Class -> String
- toHsClassDeleteFnPtrName :: Class -> String
- toHsMethodName :: Class -> Method -> String
- toHsMethodName' :: IsFnName String name => Class -> name -> String
- toHsCallbackCtorName :: Callback -> String
- toHsFnName :: ExtName -> String
- toArgName :: Int -> String
- data HsTypeSide
- cppTypeToHsTypeAndUse :: HsTypeSide -> Type -> Generator HsType
- getClassHaskellConversion :: Class -> Maybe ClassHaskellConversion
- prettyPrint :: Pretty a => a -> String
Documentation
Indicates who is managing the lifetime of an object via an object pointer.
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
A partially-rendered Module
. Contains all of the module's bindings, but
may be subject to further processing.
A chunk of generated Haskell code, including information about imports and exports.
Output | |
|
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.
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 #
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
).
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.
toHsDataTypeName :: Constness -> Class -> String Source #
The name of the data type that represents a pointer to an object of the given class and constness.
toHsDataCtorName :: Managed -> Constness -> Class -> String Source #
The name of a data constructor for one of the object pointer types.
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
.
toHsClassDeleteFnPtrName :: Class -> String Source #
The name of the foreign import that imports the same function as
toHsClassDeleteFnName
, but as a FunPtr
rather than an actual
function.
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.
cppTypeToHsTypeAndUse :: HsTypeSide -> Type -> Generator HsType Source #
getClassHaskellConversion :: Class -> Maybe ClassHaskellConversion Source #
Returns the ClassHaskellConversion
of a class, if it has one.
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.