haskell-gi-0.25.0: Generate Haskell bindings for GObject Introspection capable libraries
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.GI.CodeGen.Code

Synopsis

Documentation

data Code Source #

The generated Code is a sequence of CodeTokens.

Instances

Instances details
Monoid Code Source # 
Instance details

Defined in Data.GI.CodeGen.Code

Methods

mempty :: Code #

mappend :: Code -> Code -> Code #

mconcat :: [Code] -> Code #

Semigroup Code Source # 
Instance details

Defined in Data.GI.CodeGen.Code

Methods

(<>) :: Code -> Code -> Code #

sconcat :: NonEmpty Code -> Code #

stimes :: Integral b => b -> Code -> Code #

Show Code Source # 
Instance details

Defined in Data.GI.CodeGen.Code

Methods

showsPrec :: Int -> Code -> ShowS #

show :: Code -> String #

showList :: [Code] -> ShowS #

Eq Code Source # 
Instance details

Defined in Data.GI.CodeGen.Code

Methods

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

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

Ord Code Source # 
Instance details

Defined in Data.GI.CodeGen.Code

Methods

compare :: Code -> Code -> Ordering #

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

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

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

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

max :: Code -> Code -> Code #

min :: Code -> Code -> Code #

data ModuleInfo Source #

Information on a generated module.

data ModuleFlag Source #

Flags for module code generation.

Constructors

ImplicitPrelude

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

type CodeGen excType a = ReaderT CodeGenConfig (StateT (CGState, ModuleInfo) (Except excType)) a Source #

The base type for the code generator monad. Generators that cannot throw errors are parametric in the exception type excType.

type ExcCodeGen a = CodeGen CGError a Source #

Code generators that can throw errors.

data CGError Source #

Set of errors for the code generator.

Instances

Instances details
Show CGError Source # 
Instance details

Defined in Data.GI.CodeGen.Code

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

Like evalCodeGen, but discard the resulting output value.

evalCodeGen :: Config -> Map Name API -> ModulePath -> CodeGen e a -> (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.

data BaseVersion Source #

Minimal version of base supported by a given module.

Constructors

Base47
  1. 7.0
Base48
  1. 8.0

showBaseVersion :: BaseVersion -> Text Source #

A Text representation of the given base version bound.

registerNSDependency :: Text -> CodeGen e () Source #

Mark the given dependency as used by the module.

qualified :: ModulePath -> Name -> CodeGen e 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 e Deps Source #

Return the currently loaded set of dependencies.

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

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

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

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

printCGError :: CGError -> CodeGen e () Source #

Print, as a comment, a friendly textual description of the error.

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

Increase the indent level for code generation.

increaseIndent :: CodeGen e () Source #

Increase the indentation level for the rest of the lines in the current group.

bline :: Text -> CodeGen e () Source #

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

line :: Text -> CodeGen e () Source #

Print out a (newline-terminated) line.

blank :: CodeGen e () Source #

A blank line

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

Group a set of related code.

comment :: Text -> CodeGen e () Source #

A (possibly multi line) comment, separated by newlines

cppIf :: CPPGuard -> CodeGen e a -> CodeGen e a Source #

Guard a code block with CPP code, such that it is included only if the specified feature is enabled.

data CPPGuard Source #

Possible features to test via CPP.

Constructors

CPPOverloading

Enable overloading

CPPMinVersion Text (Integer, Integer, Integer)

Require a specific version of the given package.

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

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

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

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

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

Set the language pragmas for the current module.

addLanguagePragma :: Text -> CodeGen e () Source #

Add a language pragma for the current module.

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

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

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

Set the given flags for the module.

setModuleMinBase :: BaseVersion -> CodeGen e () Source #

Set the minimum base version supported by the current module.

getFreshTypeVariable :: CodeGen e Text Source #

Get a type variable unused in the current scope.

resetTypeVariableScope :: CodeGen e () Source #

Introduce a new scope for type variable naming: the next fresh variable will be called a.

exportModule :: SymbolName -> CodeGen e () Source #

Reexport a whole module.

exportDecl :: SymbolName -> CodeGen e () Source #

Add a type declaration-related export.

export :: HaddockSection -> SymbolName -> CodeGen e () Source #

Export a symbol in the given haddock subsection.

data HaddockSection Source #

Subsection of the haddock documentation where the export should be located, or alternatively the toplevel section.

data NamedSection Source #

Known subsections. The ordering here is the ordering in which they will appear in the haddocks.

addSectionFormattedDocs :: HaddockSection -> Text -> CodeGen e () Source #

Add documentation for a given section.

prependSectionFormattedDocs :: HaddockSection -> Text -> CodeGen e () Source #

Prepend documentation at the beginning of a given section.

findAPI :: HasCallStack => Type -> CodeGen e (Maybe API) Source #

Try to find the API associated with a given type, if known.

getAPI :: HasCallStack => Type -> CodeGen e API Source #

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

getAPIs :: CodeGen e (Map Name API) Source #

Return the list of APIs available to the generator.

getC2HMap :: CodeGen e (Map CRef Hyperlink) Source #

Return the C -> Haskell available to the generator.

config :: CodeGen e Config Source #

Return the ambient configuration for the code generator.

currentModule :: CodeGen e Text Source #

Return the name of the current module.