haskell-gi-0.20.2: Generate Haskell bindings for GObject Introspection capable libraries

Safe HaskellNone
LanguageHaskell98

Data.GI.CodeGen.Code

Synopsis

Documentation

data Code Source #

Constructors

NoCode

No code

Line Text

A single line, indented to current indentation

Indent Code

Indented region

Sequence (Seq Code)

The basic sequence of code

Group Code

A grouped set of lines

Instances

Eq Code Source # 

Methods

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

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

Show Code Source # 

Methods

showsPrec :: Int -> Code -> ShowS #

show :: Code -> String #

showList :: [Code] -> ShowS #

Monoid Code Source # 

Methods

mempty :: Code #

mappend :: Code -> Code -> Code #

mconcat :: [Code] -> Code #

data ModuleInfo Source #

Information on a generated module.

Constructors

ModuleInfo 

Fields

data ModuleFlag Source #

Flags for module code generation.

Constructors

ImplicitPrelude

Use the standard prelude, instead of the haskell-gi-base short one.

type BaseCodeGen excType a = ReaderT CodeGenConfig (StateT ModuleInfo (ExceptT excType IO)) a Source #

type CodeGen a = forall e. BaseCodeGen e a Source #

The code generator monad, for generators that cannot throw errors. The fact that they cannot throw errors is encoded in the forall, which disallows any operation on the error, except discarding it or passing it along without inspecting. This last operation is useful in order to allow embedding CodeGen computations inside ExcCodeGen computations, while disallowing the opposite embedding without explicit error handling.

type ExcCodeGen a = BaseCodeGen CGError a Source #

Code generators that can throw errors.

genCode :: Config -> Map Name API -> ModulePath -> CodeGen () -> IO ModuleInfo Source #

Like evalCodeGen, but discard the resulting output value.

evalCodeGen :: Config -> Map Name API -> ModulePath -> CodeGen a -> IO (a, ModuleInfo) Source #

Run a code generator, and return the information for the generated module together with the return value of the generator.

writeModuleTree :: Bool -> Maybe FilePath -> ModuleInfo -> IO [Text] Source #

Write down the code for a module and its submodules to disk under the given base directory. It returns the list of written modules.

listModuleTree :: ModuleInfo -> [Text] Source #

Return the list of modules writeModuleTree would write, without actually writing anything to disk.

codeToText :: Code -> Text Source #

Return a text representation of the Code.

transitiveModuleDeps :: ModuleInfo -> Deps Source #

Return the transitive set of dependencies, i.e. the union of those of the module and (transitively) its submodules.

minBaseVersion :: ModuleInfo -> BaseVersion Source #

Return the minimal base version supported by the module and all its submodules.

showBaseVersion :: BaseVersion -> Text Source #

A Text representation of the given base version bound.

registerNSDependency :: Text -> CodeGen () Source #

Mark the given dependency as used by the module.

qualified :: ModulePath -> Name -> CodeGen Text Source #

Given a module name and a symbol in the module (including a proper namespace), return a qualified name for the symbol.

getDeps :: CodeGen Deps Source #

Return the currently loaded set of dependencies.

recurseWithAPIs :: Map Name API -> CodeGen () -> CodeGen () Source #

Like recurse, giving explicitly the set of loaded APIs and C to Haskell map for the subgenerator.

handleCGExc :: (CGError -> CodeGen a) -> ExcCodeGen a -> CodeGen a Source #

Try running the given action, and if it fails run fallback instead.

describeCGError :: CGError -> Text Source #

Give a friendly textual description of the error for presenting to the user.

indent :: BaseCodeGen e a -> BaseCodeGen e a Source #

Increase the indent level for code generation.

bline :: Text -> CodeGen () Source #

Print out the given line both to the normal module, and to the HsBoot file.

line :: Text -> CodeGen () Source #

Print out a (newline-terminated) line.

blank :: CodeGen () Source #

A blank line

group :: BaseCodeGen e a -> BaseCodeGen e a Source #

Group a set of related code.

hsBoot :: BaseCodeGen e a -> BaseCodeGen e a Source #

Write the given code into the .hs-boot file for the current module.

submodule :: ModulePath -> BaseCodeGen e () -> BaseCodeGen e () Source #

Run the given CodeGen in order to generate a submodule (specified an an ordered list) of the current module.

setLanguagePragmas :: [Text] -> CodeGen () Source #

Set the language pragmas for the current module.

setGHCOptions :: [Text] -> CodeGen () Source #

Set the GHC options for compiling this module (in a OPTIONS_GHC pragma).

setModuleFlags :: [ModuleFlag] -> CodeGen () Source #

Set the given flags for the module.

setModuleMinBase :: BaseVersion -> CodeGen () Source #

Set the minimum base version supported by the current module.

exportToplevel :: SymbolName -> CodeGen () Source #

Export a toplevel (i.e. belonging to no section) symbol.

exportModule :: SymbolName -> CodeGen () Source #

Reexport a whole module.

exportDecl :: SymbolName -> CodeGen () Source #

Add a type declaration-related export.

exportMethod :: HaddockSection -> SymbolName -> CodeGen () Source #

Add a method export under the given section.

exportProperty :: HaddockSection -> SymbolName -> CodeGen () Source #

Add a property-related export under the given section.

exportSignal :: HaddockSection -> SymbolName -> CodeGen () Source #

Add a signal-related export under the given section.

getAPI :: Type -> CodeGen API Source #

Find the API associated with a given type. If the API cannot be found this raises an error.

getAPIs :: CodeGen (Map Name API) Source #

Return the list of APIs available to the generator.

getC2HMap :: CodeGen (Map CRef Hyperlink) Source #

Return the C -> Haskell available to the generator.

config :: CodeGen Config Source #

Return the ambient configuration for the code generator.

currentModule :: CodeGen Text Source #

Return the name of the current module.