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 {}
- type Generator = ReaderT Env (WriterT Output (Except ErrorMsg))
- runGenerator :: Interface -> Module -> Generator a -> Either ErrorMsg (Partial, a)
- evalGenerator :: Interface -> Module -> Generator a -> Either ErrorMsg a
- execGenerator :: Interface -> Module -> Generator a -> Either ErrorMsg Partial
- renderPartial :: Partial -> String
- askInterface :: Generator Interface
- askModule :: Generator Module
- askModuleName :: Generator String
- getModuleForExtName :: ExtName -> Generator Module
- 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 ()
- addExtension :: String -> Generator ()
- sayLn :: String -> Generator ()
- saysLn :: [String] -> Generator ()
- ln :: Generator ()
- indent :: Generator a -> Generator a
- indentSpaces :: Int -> Generator a -> Generator a
- sayLet :: [Generator ()] -> Maybe (Generator ()) -> Generator ()
- toHsEnumTypeName :: CppEnum -> Generator String
- toHsEnumTypeName' :: CppEnum -> String
- toHsEnumCtorName :: CppEnum -> [String] -> Generator String
- toHsEnumCtorName' :: CppEnum -> [String] -> String
- toHsBitspaceTypeName :: Bitspace -> Generator String
- toHsBitspaceTypeName' :: Bitspace -> String
- toHsBitspaceValueName :: Bitspace -> [String] -> Generator String
- toHsBitspaceValueName' :: Bitspace -> [String] -> String
- toHsBitspaceToNumName :: Bitspace -> Generator String
- toHsBitspaceToNumName' :: Bitspace -> String
- toHsBitspaceClassName :: Bitspace -> Generator String
- toHsBitspaceClassName' :: Bitspace -> String
- toHsBitspaceFromValueName :: Bitspace -> Generator String
- toHsBitspaceFromValueName' :: Bitspace -> String
- toHsValueClassName :: Class -> Generator String
- toHsValueClassName' :: Class -> String
- toHsWithValuePtrName :: Class -> Generator String
- toHsWithValuePtrName' :: Class -> String
- toHsPtrClassName :: Constness -> Class -> Generator String
- toHsPtrClassName' :: Constness -> Class -> String
- toHsCastMethodName :: Constness -> Class -> Generator String
- toHsCastMethodName' :: Constness -> Class -> String
- toHsDownCastClassName :: Constness -> Class -> Generator String
- toHsDownCastClassName' :: Constness -> Class -> String
- toHsDownCastMethodName :: Constness -> Class -> Generator String
- toHsDownCastMethodName' :: Constness -> Class -> String
- toHsCastPrimitiveName :: Class -> Class -> Class -> Generator String
- toHsCastPrimitiveName' :: Class -> Class -> String
- toHsConstCastFnName :: Constness -> Class -> Generator String
- toHsConstCastFnName' :: Constness -> Class -> String
- toHsDataTypeName :: Constness -> Class -> Generator String
- toHsDataTypeName' :: Constness -> Class -> String
- toHsDataCtorName :: Managed -> Constness -> Class -> Generator String
- toHsDataCtorName' :: Managed -> Constness -> Class -> String
- toHsClassDeleteFnName' :: Class -> String
- toHsClassDeleteFnPtrName' :: Class -> String
- toHsCtorName :: Class -> Ctor -> Generator String
- toHsCtorName' :: Class -> Ctor -> String
- toHsMethodName :: Class -> Method -> Generator String
- toHsMethodName' :: Class -> Method -> String
- toHsClassEntityName :: IsFnName String name => Class -> name -> Generator String
- toHsClassEntityName' :: IsFnName String name => Class -> name -> String
- toHsCallbackCtorName :: Callback -> Generator String
- toHsCallbackCtorName' :: Callback -> String
- toHsCallbackNewFunPtrFnName :: Callback -> Generator String
- toHsCallbackNewFunPtrFnName' :: Callback -> String
- toHsFnName :: ExtName -> Generator String
- toHsFnName' :: ExtName -> String
- toArgName :: Int -> String
- data HsTypeSide
- cppTypeToHsTypeAndUse :: HsTypeSide -> Type -> Generator HsType
- getClassHaskellConversion :: Class -> ClassHaskellConversion
- callbackToTFn :: HsTypeSide -> Callback -> Generator Type
- 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.
Partial | |
|
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 -> 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 -> Module -> Generator a -> Either ErrorMsg a Source #
Runs a generator action and returns the its value.
execGenerator :: Interface -> Module -> Generator a -> Either ErrorMsg Partial Source #
Runs a generator action and returns its output.
askInterface :: Generator Interface Source #
Returns the currently generating interface.
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 #
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
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.
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.
toHsEnumTypeName' :: CppEnum -> String Source #
Pure version of toHsEnumTypeName
that doesn't create a qualified name.
toHsEnumCtorName :: CppEnum -> [String] -> Generator 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
.
toHsEnumCtorName' :: CppEnum -> [String] -> String Source #
Pure version of toHsEnumCtorName
that doesn't create a qualified name.
toHsBitspaceTypeName :: Bitspace -> Generator String Source #
Returns the Haskell name for a bitspace. See toHsEnumTypeName
.
toHsBitspaceTypeName' :: Bitspace -> String Source #
Pure version of toHsBitspaceTypeName
that doesn't create a qualified name.
toHsBitspaceValueName :: Bitspace -> [String] -> Generator String Source #
Constructs the data constructor name for a value in a bitspace. See
toHsEnumCtorName
.
toHsBitspaceValueName' :: Bitspace -> [String] -> String Source #
Pure version of toHsBitspaceValueName
that doesn't create a qualified name.
toHsBitspaceToNumName :: Bitspace -> Generator String Source #
Returns the name of the function that will convert a bitspace value into a raw numeric value.
toHsBitspaceToNumName' :: Bitspace -> String Source #
Pure version of toHsBitspaceToNumName
that doesn't create a qualified name.
toHsBitspaceClassName :: Bitspace -> Generator String Source #
The name of the Haskell typeclass that contains a method for converting to a bitspace value.
toHsBitspaceClassName' :: Bitspace -> String Source #
Pure version of toHsBitspaceClassName
that doesn't create a qualified name.
toHsBitspaceFromValueName :: Bitspace -> Generator String Source #
The name of the method in the toHsBitspaceClassName
typeclass that
constructs bitspace values.
toHsBitspaceFromValueName' :: Bitspace -> String Source #
Pure version of toHsBitspaceFromValueName
that doesn't create a qualified name.
toHsValueClassName :: Class -> Generator String Source #
The name for the typeclass of types that can be represented as values of the given C++ class.
toHsValueClassName' :: Class -> String Source #
Pure version of toHsValueClassName
that doesn't create a qualified name.
toHsWithValuePtrName :: Class -> Generator String Source #
The name of the method within the toHsValueClassName
typeclass for
accessing an object of the type as a pointer.
toHsWithValuePtrName' :: Class -> String Source #
Pure version of toHsWithValuePtrName
that doesn't create a qualified name.
toHsPtrClassName :: Constness -> Class -> Generator String Source #
The name for the typeclass of types that are (possibly const) pointers to objects of the given C++ class, or subclasses.
toHsPtrClassName' :: Constness -> Class -> String Source #
Pure version of toHsPtrClassName
that doesn't create a qualified name.
toHsCastMethodName :: Constness -> Class -> Generator String Source #
The name of the function that upcasts pointers to the specific class type and constness.
toHsCastMethodName' :: Constness -> Class -> String Source #
Pure version of toHsCastMethodName
that doesn't create a qualified name.
toHsDownCastClassName :: Constness -> Class -> Generator String Source #
The name of the typeclass that provides a method to downcast to a specific
class type. See toHsDownCastMethodName
.
toHsDownCastClassName' :: Constness -> Class -> String Source #
Pure version of toHsDownCastClassName
that doesn't create a qualified
name.
toHsDownCastMethodName :: Constness -> Class -> Generator String Source #
The name of the function that downcasts pointers to the specific class type and constness.
toHsDownCastMethodName' :: Constness -> Class -> String Source #
Pure version of toHsDownCastMethodName
that doesn't create a qualified
name.
toHsCastPrimitiveName :: Class -> Class -> Class -> Generator String Source #
The import name for the foreign function that casts between two specific pointer types. Used for upcasting and downcasting.
We need to know which module the cast function resides in, and while we could look this up, the caller always knows, so we just have them pass it in.
toHsCastPrimitiveName' :: Class -> Class -> String Source #
Pure version of toHsCastPrimitiveName
that doesn't create a qualified
name.
toHsConstCastFnName' :: Constness -> Class -> String Source #
Pure version of toHsConstCastFnName
that doesn't create a qualified name.
toHsDataTypeName :: Constness -> Class -> Generator String Source #
The name of the data type that represents a pointer to an object of the given class and constness.
toHsDataTypeName' :: Constness -> Class -> String Source #
Pure version of toHsDataTypeName
that doesn't create a qualified name.
toHsDataCtorName :: Managed -> Constness -> Class -> Generator String Source #
The name of a data constructor for one of the object pointer types.
toHsDataCtorName' :: Managed -> Constness -> Class -> String Source #
Pure version of toHsDataCtorName
that doesn't create a qualified name.
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
.
This is internal to a generated Haskell module, so it does not have a public (qualified) form.
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.
This is internal to a generated Haskell module, so it does not have a public (qualified) form.
toHsCtorName :: Class -> Ctor -> Generator String Source #
Returns the name of the Haskell function that invokes the given constructor.
toHsCtorName' :: Class -> Ctor -> String Source #
Pure version of toHsCtorName
that doesn't create a qualified name.
toHsMethodName :: Class -> Method -> Generator String Source #
Returns the name of the Haskell function that invokes the given method.
toHsMethodName' :: Class -> Method -> String Source #
Pure version of toHsMethodName
that doesn't create a qualified name.
toHsClassEntityName :: IsFnName String name => Class -> name -> Generator String Source #
Returns the name of the Haskell function for an entity in a class.
toHsClassEntityName' :: IsFnName String name => Class -> name -> String Source #
Pure version of toHsClassEntityName
that doesn't create a qualified name.
toHsCallbackCtorName :: Callback -> Generator 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.
toHsCallbackCtorName' :: Callback -> String Source #
Pure version of toHsCallbackCtorName
that doesn't create a qualified
name.
toHsCallbackNewFunPtrFnName :: Callback -> Generator String Source #
The name of the function that takes a Haskell function with Haskell-side
types and wraps it in a FunPtr
that does appropriate
conversions to and from C-side types.
toHsCallbackNewFunPtrFnName' :: Callback -> String Source #
Pure version of toHsCallbackNewFunPtrFnName
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.
cppTypeToHsTypeAndUse :: HsTypeSide -> Type -> Generator HsType Source #
getClassHaskellConversion :: Class -> ClassHaskellConversion Source #
Returns the ClassHaskellConversion
of a class.
callbackToTFn :: HsTypeSide -> Callback -> Generator Type Source #
Constructs the function type for a callback. For Haskell, the type depends on the side; the C++ side has additional parameters.
Keep this in sync with the C++ generator's version.
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.