Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Code
- data ModuleInfo
- data ModuleFlag = ImplicitPrelude
- type CodeGen excType a = ReaderT CodeGenConfig (StateT (CGState, ModuleInfo) (Except excType)) a
- type ExcCodeGen a = CodeGen CGError a
- data CGError
- genCode :: Config -> Map Name API -> ModulePath -> CodeGen e () -> ModuleInfo
- evalCodeGen :: Config -> Map Name API -> ModulePath -> CodeGen e 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 e ()
- qualified :: ModulePath -> Name -> CodeGen e Text
- getDeps :: CodeGen e Deps
- recurseWithAPIs :: Map Name API -> CodeGen e () -> CodeGen e ()
- handleCGExc :: (CGError -> CodeGen e a) -> ExcCodeGen a -> CodeGen e a
- printCGError :: CGError -> CodeGen e ()
- notImplementedError :: Text -> ExcCodeGen a
- badIntroError :: Text -> ExcCodeGen a
- missingInfoError :: Text -> ExcCodeGen a
- indent :: CodeGen e a -> CodeGen e a
- increaseIndent :: CodeGen e ()
- bline :: Text -> CodeGen e ()
- line :: Text -> CodeGen e ()
- blank :: CodeGen e ()
- group :: CodeGen e a -> CodeGen e a
- comment :: Text -> CodeGen e ()
- cppIf :: CPPGuard -> CodeGen e a -> CodeGen e a
- data CPPGuard
- hsBoot :: CodeGen e a -> CodeGen e a
- submodule :: ModulePath -> CodeGen e () -> CodeGen e ()
- setLanguagePragmas :: [Text] -> CodeGen e ()
- addLanguagePragma :: Text -> CodeGen e ()
- setGHCOptions :: [Text] -> CodeGen e ()
- setModuleFlags :: [ModuleFlag] -> CodeGen e ()
- setModuleMinBase :: BaseVersion -> CodeGen e ()
- getFreshTypeVariable :: CodeGen e Text
- resetTypeVariableScope :: CodeGen e ()
- exportModule :: SymbolName -> CodeGen e ()
- exportDecl :: SymbolName -> CodeGen e ()
- export :: HaddockSection -> SymbolName -> CodeGen e ()
- data HaddockSection
- data NamedSection
- addSectionFormattedDocs :: HaddockSection -> Text -> CodeGen e ()
- prependSectionFormattedDocs :: HaddockSection -> Text -> CodeGen e ()
- findAPI :: HasCallStack => Type -> CodeGen e (Maybe API)
- getAPI :: HasCallStack => Type -> CodeGen e API
- findAPIByName :: HasCallStack => Name -> CodeGen e API
- getAPIs :: CodeGen e (Map Name API)
- getC2HMap :: CodeGen e (Map CRef Hyperlink)
- config :: CodeGen e Config
- currentModule :: CodeGen e 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
Show ModuleFlag Source # | |
Defined in Data.GI.CodeGen.Code showsPrec :: Int -> ModuleFlag -> ShowS # show :: ModuleFlag -> String # showList :: [ModuleFlag] -> ShowS # | |
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 # |
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.
Set of errors for the code generator.
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.
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
Show BaseVersion Source # | |
Defined in Data.GI.CodeGen.Code showsPrec :: Int -> BaseVersion -> ShowS # show :: BaseVersion -> String # showList :: [BaseVersion] -> ShowS # | |
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 # |
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.
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.
notImplementedError :: Text -> ExcCodeGen a Source #
badIntroError :: Text -> ExcCodeGen a Source #
missingInfoError :: Text -> ExcCodeGen a Source #
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.
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.
Possible features to test via CPP.
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.
Instances
Show HaddockSection Source # | |
Defined in Data.GI.CodeGen.Code showsPrec :: Int -> HaddockSection -> ShowS # show :: HaddockSection -> String # showList :: [HaddockSection] -> ShowS # | |
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 # |
data NamedSection Source #
Known subsections. The ordering here is the ordering in which they will appear in the haddocks.
Instances
Show NamedSection Source # | |
Defined in Data.GI.CodeGen.Code showsPrec :: Int -> NamedSection -> ShowS # show :: NamedSection -> String # showList :: [NamedSection] -> ShowS # | |
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 # |
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
.
findAPIByName :: HasCallStack => Name -> CodeGen e API Source #
getC2HMap :: CodeGen e (Map CRef Hyperlink) Source #
Return the C -> Haskell available to the generator.
currentModule :: CodeGen e Text Source #
Return the name of the current module.