Safe Haskell | None |
---|---|
Language | Haskell2010 |
Shared portion of the Haskell code generator. Usable by binding definitions.
Synopsis
- 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
- data Env = Env {}
- 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 ()
- data SayExportMode
- sayLn :: String -> Generator ()
- saysLn :: [String] -> Generator ()
- ln :: Generator ()
- indent :: Generator a -> Generator a
- indentSpaces :: Int -> Generator a -> Generator a
- sayLet :: [Generator ()] -> Maybe (Generator ()) -> Generator ()
- getExtNameModule :: ExtName -> Generator Module
- addExtNameModule :: ExtName -> String -> Generator String
- toHsTypeName :: Constness -> ExtName -> Generator String
- toHsTypeName' :: Constness -> ExtName -> String
- toHsFnName :: ExtName -> Generator String
- toHsFnName' :: ExtName -> String
- toArgName :: Int -> String
- data HsTypeSide
- cppTypeToHsTypeAndUse :: HsTypeSide -> Type -> Generator HsType
- getClassHaskellConversion :: Class -> ClassHaskellConversion
- getEffectiveExceptionHandlers :: ExceptionHandlers -> Generator ExceptionHandlers
- prettyPrint :: Pretty a => a -> String
Documentation
Indicates who is managing the lifetime of an object via an object pointer.
Unmanaged | The object's lifetime is being managed manually. |
Managed | The object's lifetime is being managed by the Haskell garbage collector. |
Instances
Bounded Managed Source # | |
Enum Managed Source # | |
Eq Managed Source # | |
Ord Managed Source # | |
Defined in Foreign.Hoppy.Generator.Language.Haskell |
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.
Context information for generating Haskell code.
Env | |
|
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
data SayExportMode Source #
The section of code that Hoppy is generating, for an export.
SayExportForeignImports | Hoppy is generating |
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 |
SayExportBoot | If Hoppy needs to generate For information on the special format of |
Instances
Eq SayExportMode Source # | |
Defined in Foreign.Hoppy.Generator.Language.Haskell (==) :: SayExportMode -> SayExportMode -> Bool # (/=) :: SayExportMode -> SayExportMode -> Bool # | |
Show SayExportMode Source # | |
Defined in Foreign.Hoppy.Generator.Language.Haskell showsPrec :: Int -> SayExportMode -> ShowS # show :: SayExportMode -> String # showList :: [SayExportMode] -> ShowS # |
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.
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.
Instances
Eq HsTypeSide Source # | |
Defined in Foreign.Hoppy.Generator.Language.Haskell (==) :: HsTypeSide -> HsTypeSide -> Bool # (/=) :: HsTypeSide -> HsTypeSide -> Bool # | |
Show HsTypeSide Source # | |
Defined in Foreign.Hoppy.Generator.Language.Haskell showsPrec :: Int -> HsTypeSide -> ShowS # show :: HsTypeSide -> String # showList :: [HsTypeSide] -> ShowS # |
cppTypeToHsTypeAndUse :: HsTypeSide -> Type -> Generator HsType Source #
getClassHaskellConversion :: Class -> ClassHaskellConversion Source #
Returns the ClassHaskellConversion
of a class.
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.