Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data Code
- data ModuleInfo
- data ModuleFlag = ImplicitPrelude
- type BaseCodeGen excType a = ReaderT CodeGenConfig (StateT (CGState, ModuleInfo) (Except excType)) a
- type CodeGen a = forall e. BaseCodeGen e a
- type ExcCodeGen a = BaseCodeGen CGError a
- data CGError
- genCode :: Config -> Map Name API -> ModulePath -> CodeGen () -> ModuleInfo
- evalCodeGen :: Config -> Map Name API -> ModulePath -> CodeGen a -> (a, ModuleInfo)
- writeModuleTree :: Bool -> Maybe FilePath -> ModuleInfo -> IO [Text]
- listModuleTree :: ModuleInfo -> [Text]
- codeToText :: Code -> Text
- transitiveModuleDeps :: ModuleInfo -> Deps
- minBaseVersion :: ModuleInfo -> BaseVersion
- data BaseVersion
- showBaseVersion :: BaseVersion -> Text
- registerNSDependency :: Text -> CodeGen ()
- qualified :: ModulePath -> Name -> CodeGen Text
- getDeps :: CodeGen Deps
- recurseWithAPIs :: Map Name API -> CodeGen () -> CodeGen ()
- handleCGExc :: (CGError -> CodeGen a) -> ExcCodeGen a -> CodeGen a
- describeCGError :: CGError -> Text
- notImplementedError :: Text -> ExcCodeGen a
- badIntroError :: Text -> ExcCodeGen a
- missingInfoError :: Text -> ExcCodeGen a
- indent :: BaseCodeGen e a -> BaseCodeGen e a
- increaseIndent :: CodeGen ()
- bline :: Text -> CodeGen ()
- line :: Text -> CodeGen ()
- blank :: CodeGen ()
- group :: BaseCodeGen e a -> BaseCodeGen e a
- cppIf :: CPPGuard -> BaseCodeGen e a -> BaseCodeGen e a
- data CPPGuard = CPPOverloading
- hsBoot :: BaseCodeGen e a -> BaseCodeGen e a
- submodule :: ModulePath -> BaseCodeGen e () -> BaseCodeGen e ()
- setLanguagePragmas :: [Text] -> CodeGen ()
- setGHCOptions :: [Text] -> CodeGen ()
- setModuleFlags :: [ModuleFlag] -> CodeGen ()
- setModuleMinBase :: BaseVersion -> CodeGen ()
- getFreshTypeVariable :: CodeGen Text
- resetTypeVariableScope :: CodeGen ()
- exportModule :: SymbolName -> CodeGen ()
- exportDecl :: SymbolName -> CodeGen ()
- export :: HaddockSection -> SymbolName -> CodeGen ()
- data HaddockSection
- data NamedSection
- addSectionFormattedDocs :: HaddockSection -> Text -> CodeGen ()
- findAPI :: Type -> CodeGen (Maybe API)
- getAPI :: Type -> CodeGen API
- findAPIByName :: Name -> CodeGen API
- getAPIs :: CodeGen (Map Name API)
- getC2HMap :: CodeGen (Map CRef Hyperlink)
- config :: CodeGen Config
- currentModule :: CodeGen Text
Documentation
The generated Code
is a sequence of CodeToken
s.
data ModuleInfo Source #
Information on a generated module.
data ModuleFlag Source #
Flags for module code generation.
ImplicitPrelude | Use the standard prelude, instead of the haskell-gi-base short one. |
Instances
Eq ModuleFlag Source # | |
Defined in Data.GI.CodeGen.Code (==) :: ModuleFlag -> ModuleFlag -> Bool # (/=) :: ModuleFlag -> ModuleFlag -> Bool # | |
Ord ModuleFlag Source # | |
Defined in Data.GI.CodeGen.Code compare :: ModuleFlag -> ModuleFlag -> Ordering # (<) :: ModuleFlag -> ModuleFlag -> Bool # (<=) :: ModuleFlag -> ModuleFlag -> Bool # (>) :: ModuleFlag -> ModuleFlag -> Bool # (>=) :: ModuleFlag -> ModuleFlag -> Bool # max :: ModuleFlag -> ModuleFlag -> ModuleFlag # min :: ModuleFlag -> ModuleFlag -> ModuleFlag # | |
Show ModuleFlag Source # | |
Defined in Data.GI.CodeGen.Code showsPrec :: Int -> ModuleFlag -> ShowS # show :: ModuleFlag -> String # showList :: [ModuleFlag] -> ShowS # |
type BaseCodeGen excType a = ReaderT CodeGenConfig (StateT (CGState, ModuleInfo) (Except excType)) a Source #
The base type for the code generator monad.
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.
Set of errors for the code generator.
genCode :: Config -> Map Name API -> ModulePath -> CodeGen () -> ModuleInfo Source #
Like evalCodeGen
, but discard the resulting output value.
evalCodeGen :: Config -> Map Name API -> ModulePath -> CodeGen 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.
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.
Instances
Eq BaseVersion Source # | |
Defined in Data.GI.CodeGen.Code (==) :: BaseVersion -> BaseVersion -> Bool # (/=) :: BaseVersion -> BaseVersion -> Bool # | |
Ord BaseVersion Source # | |
Defined in Data.GI.CodeGen.Code compare :: BaseVersion -> BaseVersion -> Ordering # (<) :: BaseVersion -> BaseVersion -> Bool # (<=) :: BaseVersion -> BaseVersion -> Bool # (>) :: BaseVersion -> BaseVersion -> Bool # (>=) :: BaseVersion -> BaseVersion -> Bool # max :: BaseVersion -> BaseVersion -> BaseVersion # min :: BaseVersion -> BaseVersion -> BaseVersion # | |
Show BaseVersion Source # | |
Defined in Data.GI.CodeGen.Code showsPrec :: Int -> BaseVersion -> ShowS # show :: BaseVersion -> String # showList :: [BaseVersion] -> ShowS # |
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.
recurseWithAPIs :: Map Name API -> CodeGen () -> CodeGen () Source #
Like recurseCG
, 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.
notImplementedError :: Text -> ExcCodeGen a Source #
badIntroError :: Text -> ExcCodeGen a Source #
missingInfoError :: Text -> ExcCodeGen a Source #
indent :: BaseCodeGen e a -> BaseCodeGen e a Source #
Increase the indent level for code generation.
increaseIndent :: CodeGen () Source #
Increase the indentation level for the rest of the lines in the current group.
bline :: Text -> CodeGen () Source #
Print out the given line both to the normal module, and to the HsBoot file.
group :: BaseCodeGen e a -> BaseCodeGen e a Source #
Group a set of related code.
cppIf :: CPPGuard -> BaseCodeGen e a -> BaseCodeGen e a Source #
Guard a code block with CPP code, such that it is included only if the specified feature is enabled.
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.
getFreshTypeVariable :: CodeGen Text Source #
Get a type variable unused in the current scope.
resetTypeVariableScope :: CodeGen () Source #
Introduce a new scope for type variable naming: the next fresh
variable will be called a
.
exportModule :: SymbolName -> CodeGen () Source #
Reexport a whole module.
exportDecl :: SymbolName -> CodeGen () Source #
Add a type declaration-related export.
export :: HaddockSection -> SymbolName -> CodeGen () 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.
Instances
Eq HaddockSection Source # | |
Defined in Data.GI.CodeGen.Code (==) :: HaddockSection -> HaddockSection -> Bool # (/=) :: HaddockSection -> HaddockSection -> Bool # | |
Ord HaddockSection Source # | |
Defined in Data.GI.CodeGen.Code compare :: HaddockSection -> HaddockSection -> Ordering # (<) :: HaddockSection -> HaddockSection -> Bool # (<=) :: HaddockSection -> HaddockSection -> Bool # (>) :: HaddockSection -> HaddockSection -> Bool # (>=) :: HaddockSection -> HaddockSection -> Bool # max :: HaddockSection -> HaddockSection -> HaddockSection # min :: HaddockSection -> HaddockSection -> HaddockSection # | |
Show HaddockSection Source # | |
Defined in Data.GI.CodeGen.Code showsPrec :: Int -> HaddockSection -> ShowS # show :: HaddockSection -> String # showList :: [HaddockSection] -> ShowS # |
data NamedSection Source #
Known subsections. The ordering here is the ordering in which they will appear in the haddocks.
Instances
Eq NamedSection Source # | |
Defined in Data.GI.CodeGen.Code (==) :: NamedSection -> NamedSection -> Bool # (/=) :: NamedSection -> NamedSection -> Bool # | |
Ord NamedSection Source # | |
Defined in Data.GI.CodeGen.Code compare :: NamedSection -> NamedSection -> Ordering # (<) :: NamedSection -> NamedSection -> Bool # (<=) :: NamedSection -> NamedSection -> Bool # (>) :: NamedSection -> NamedSection -> Bool # (>=) :: NamedSection -> NamedSection -> Bool # max :: NamedSection -> NamedSection -> NamedSection # min :: NamedSection -> NamedSection -> NamedSection # | |
Show NamedSection Source # | |
Defined in Data.GI.CodeGen.Code showsPrec :: Int -> NamedSection -> ShowS # show :: NamedSection -> String # showList :: [NamedSection] -> ShowS # |
addSectionFormattedDocs :: HaddockSection -> Text -> CodeGen () Source #
Add documentation for a 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
.
getC2HMap :: CodeGen (Map CRef Hyperlink) Source #
Return the C -> Haskell available to the generator.
currentModule :: CodeGen Text Source #
Return the name of the current module.