Copyright | (c) David Waern 2010 |
---|---|
License | BSD-like |
Maintainer | haddock@projects.haskellorg |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
The Haddock API: A rudimentory, highly experimental API exposing some of the internals of Haddock. Don't expect it to be stable.
- data Interface = Interface {
- ifaceMod :: !Module
- ifaceOrigFilename :: !FilePath
- ifaceInfo :: !(HaddockModInfo Name)
- ifaceDoc :: !(Documentation Name)
- ifaceRnDoc :: !(Documentation DocName)
- ifaceOptions :: ![DocOption]
- ifaceDeclMap :: !(Map Name [LHsDecl Name])
- ifaceDocMap :: !(DocMap Name)
- ifaceArgMap :: !(ArgMap Name)
- ifaceRnDocMap :: !(DocMap DocName)
- ifaceRnArgMap :: !(ArgMap DocName)
- ifaceSubMap :: !(Map Name [Name])
- ifaceFixMap :: !(Map Name Fixity)
- ifaceExportItems :: ![ExportItem Name]
- ifaceRnExportItems :: ![ExportItem DocName]
- ifaceExports :: ![Name]
- ifaceVisibleExports :: ![Name]
- ifaceModuleAliases :: !AliasMap
- ifaceInstances :: ![ClsInst]
- ifaceFamInstances :: ![FamInst]
- ifaceOrphanInstances :: ![DocInstance Name]
- ifaceRnOrphanInstances :: ![DocInstance DocName]
- ifaceHaddockCoverage :: !(Int, Int)
- ifaceWarningMap :: !WarningMap
- ifaceTokenizedSrc :: !(Maybe [RichToken])
- data InstalledInterface = InstalledInterface {
- instMod :: Module
- instInfo :: HaddockModInfo Name
- instDocMap :: DocMap Name
- instArgMap :: ArgMap Name
- instExports :: [Name]
- instVisibleExports :: [Name]
- instOptions :: [DocOption]
- instSubMap :: Map Name [Name]
- instFixMap :: Map Name Fixity
- toInstalledIface :: Interface -> InstalledInterface
- createInterfaces :: [Flag] -> [String] -> IO [Interface]
- processModules :: Verbosity -> [String] -> [Flag] -> [InterfaceFile] -> Ghc ([Interface], LinkEnv)
- data ExportItem name
- = ExportDecl {
- expItemDecl :: !(LHsDecl name)
- expItemMbDoc :: !(DocForDecl name)
- expItemSubDocs :: ![(name, DocForDecl name)]
- expItemInstances :: ![DocInstance name]
- expItemFixities :: ![(name, Fixity)]
- expItemSpliced :: !Bool
- | ExportNoDecl {
- expItemName :: !name
- expItemSubs :: ![name]
- | ExportGroup {
- expItemSectionLevel :: !Int
- expItemSectionId :: !String
- expItemSectionText :: !(Doc name)
- | ExportDoc !(MDoc name)
- | ExportModule !Module
- = ExportDecl {
- type DocForDecl name = (Documentation name, FnArgsDoc name)
- type FnArgsDoc name = Map Int (MDoc name)
- type LinkEnv = Map Name Module
- data DocName
- type DocInstance name = (InstHead name, Maybe (MDoc name), Located name)
- data InstHead name
- type Doc id = DocH (ModuleName, OccName) id
- type MDoc id = MetaDoc (ModuleName, OccName) id
- data DocH mod id :: * -> * -> *
- = DocEmpty
- | DocAppend (DocH mod id) (DocH mod id)
- | DocString String
- | DocParagraph (DocH mod id)
- | DocIdentifier id
- | DocIdentifierUnchecked mod
- | DocModule String
- | DocWarning (DocH mod id)
- | DocEmphasis (DocH mod id)
- | DocMonospaced (DocH mod id)
- | DocBold (DocH mod id)
- | DocUnorderedList [DocH mod id]
- | DocOrderedList [DocH mod id]
- | DocDefList [(DocH mod id, DocH mod id)]
- | DocCodeBlock (DocH mod id)
- | DocHyperlink Hyperlink
- | DocPic Picture
- | DocMathInline String
- | DocMathDisplay String
- | DocAName String
- | DocProperty String
- | DocExamples [Example]
- | DocHeader (Header (DocH mod id))
- data Example :: * = Example {}
- data Hyperlink :: * = Hyperlink {}
- data DocMarkup id a = Markup {
- markupEmpty :: a
- markupString :: String -> a
- markupParagraph :: a -> a
- markupAppend :: a -> a -> a
- markupIdentifier :: id -> a
- markupIdentifierUnchecked :: (ModuleName, OccName) -> a
- markupModule :: String -> a
- markupWarning :: a -> a
- markupEmphasis :: a -> a
- markupBold :: a -> a
- markupMonospaced :: a -> a
- markupUnorderedList :: [a] -> a
- markupOrderedList :: [a] -> a
- markupDefList :: [(a, a)] -> a
- markupCodeBlock :: a -> a
- markupHyperlink :: Hyperlink -> a
- markupAName :: String -> a
- markupPic :: Picture -> a
- markupMathInline :: String -> a
- markupMathDisplay :: String -> a
- markupProperty :: String -> a
- markupExample :: [Example] -> a
- markupHeader :: Header a -> a
- data Documentation name = Documentation {
- documentationDoc :: Maybe (MDoc name)
- documentationWarning :: !(Maybe (Doc name))
- type ArgMap a = Map Name (Map Int (MDoc a))
- type AliasMap = Map Module ModuleName
- type WarningMap = Map Name (Doc Name)
- type DocMap a = Map Name (MDoc a)
- data HaddockModInfo name = HaddockModInfo {}
- markup :: DocMarkup id a -> Doc id -> a
- data InterfaceFile = InterfaceFile {}
- readInterfaceFile :: forall m. MonadIO m => NameCacheAccessor m -> FilePath -> m (Either String InterfaceFile)
- nameCacheFromGhc :: NameCacheAccessor Ghc
- freshNameCache :: NameCacheAccessor IO
- type NameCacheAccessor m = (m NameCache, NameCache -> m ())
- data Flag
- = Flag_BuiltInThemes
- | Flag_CSS String
- | Flag_ReadInterface String
- | Flag_DumpInterface String
- | Flag_Heading String
- | Flag_Html
- | Flag_Hoogle
- | Flag_Lib String
- | Flag_OutputDir FilePath
- | Flag_Prologue FilePath
- | Flag_SourceBaseURL String
- | Flag_SourceModuleURL String
- | Flag_SourceEntityURL String
- | Flag_SourceLEntityURL String
- | Flag_WikiBaseURL String
- | Flag_WikiModuleURL String
- | Flag_WikiEntityURL String
- | Flag_LaTeX
- | Flag_LaTeXStyle String
- | Flag_HyperlinkedSource
- | Flag_SourceCss String
- | Flag_Mathjax String
- | Flag_Help
- | Flag_Verbosity String
- | Flag_Version
- | Flag_CompatibleInterfaceVersions
- | Flag_InterfaceVersion
- | Flag_UseContents String
- | Flag_GenContents
- | Flag_UseIndex String
- | Flag_GenIndex
- | Flag_IgnoreAllExports
- | Flag_HideModule String
- | Flag_ShowExtensions String
- | Flag_OptGhc String
- | Flag_GhcLibDir String
- | Flag_GhcVersion
- | Flag_PrintGhcPath
- | Flag_PrintGhcLibDir
- | Flag_NoWarnings
- | Flag_UseUnicode
- | Flag_NoTmpCompDir
- | Flag_Qualification String
- | Flag_PrettyHtml
- | Flag_NoPrintMissingDocs
- | Flag_PackageName String
- | Flag_PackageVersion String
- data DocOption
- data HaddockException = HaddockException String
- haddock :: [String] -> IO ()
- haddockWithGhc :: (forall a. [Flag] -> Ghc a -> IO a) -> [String] -> IO ()
- getGhcDirs :: [Flag] -> IO (String, String)
- withGhc :: [Flag] -> Ghc a -> IO a
Interface
Interface
holds all information used to render a single Haddock page.
It represents the interface of a module. The core business of Haddock
lies in creating this structure. Note that the record contains some fields
that are only used to create the final record, and that are not used by the
backends.
Interface | |
|
data InstalledInterface Source #
A subset of the fields of Interface
that we store in the interface
files.
InstalledInterface | |
|
toInstalledIface :: Interface -> InstalledInterface Source #
Convert an Interface
to an InstalledInterface
:: Verbosity | Verbosity of logging to |
-> [String] | A list of file or module names sorted by module topology |
-> [Flag] | Command-line flags |
-> [InterfaceFile] | Interface files of package dependencies |
-> Ghc ([Interface], LinkEnv) | Resulting list of interfaces and renaming environment |
Create Interface
s and a link environment by typechecking the list of
modules using the GHC API and processing the resulting syntax trees.
Export items & declarations
data ExportItem name Source #
ExportDecl | An exported declaration. |
| |
ExportNoDecl | An exported entity for which we have no documentation (perhaps because it resides in another package). |
| |
ExportGroup | A section heading. |
| |
ExportDoc !(MDoc name) | Some documentation. |
ExportModule !Module | A cross-reference to another module. |
type DocForDecl name = (Documentation name, FnArgsDoc name) Source #
type FnArgsDoc name = Map Int (MDoc name) Source #
Arguments and result are indexed by Int, zero-based from the left, because that's the easiest to use when recursing over types.
Cross-referencing
type LinkEnv = Map Name Module Source #
Type of environment used to cross-reference identifiers in the syntax.
Extends Name
with cross-reference information.
Documented Name Module | This thing is part of the (existing or resulting)
documentation. The |
Undocumented Name | This thing is not part of the (existing or resulting) documentation, as far as Haddock knows. |
Eq DocName Source # | |
Data DocName Source # | |
NamedThing DocName Source # | |
Outputable DocName Source # | Useful for debugging |
OutputableBndr DocName Source # | |
type PostTc DocName Type Source # | |
type PostTc DocName Type Source # | |
type PostTc DocName Coercion Source # | |
type PostTc DocName Coercion Source # | |
type PostTc DocName Kind Source # | |
type PostTc DocName Kind Source # | |
type PostRn DocName Bool Source # | |
type PostRn DocName Bool Source # | |
type PostRn DocName NameSet Source # | |
type PostRn DocName NameSet Source # | |
type PostRn DocName Fixity Source # | |
type PostRn DocName Fixity Source # | |
type PostRn DocName Name Source # | |
type PostRn DocName DocName Source # | |
type PostRn DocName [Name] Source # | |
type PostRn DocName [Name] Source # | |
type PostRn DocName (Located Name) Source # | |
Instances
type DocInstance name = (InstHead name, Maybe (MDoc name), Located name) Source #
An instance head that may have documentation and a source location.
The head of an instance. Consists of a class name, a list of kind parameters, a list of type parameters and an instance type
Documentation comments
type MDoc id = MetaDoc (ModuleName, OccName) id Source #
data DocH mod id :: * -> * -> * #
DocEmpty | |
DocAppend (DocH mod id) (DocH mod id) | |
DocString String | |
DocParagraph (DocH mod id) | |
DocIdentifier id | |
DocIdentifierUnchecked mod | |
DocModule String | |
DocWarning (DocH mod id) | |
DocEmphasis (DocH mod id) | |
DocMonospaced (DocH mod id) | |
DocBold (DocH mod id) | |
DocUnorderedList [DocH mod id] | |
DocOrderedList [DocH mod id] | |
DocDefList [(DocH mod id, DocH mod id)] | |
DocCodeBlock (DocH mod id) | |
DocHyperlink Hyperlink | |
DocPic Picture | |
DocMathInline String | |
DocMathDisplay String | |
DocAName String | |
DocProperty String | |
DocExamples [Example] | |
DocHeader (Header (DocH mod id)) |
Markup | |
|
data Documentation name Source #
Documentation | |
|
data HaddockModInfo name Source #
HaddockModInfo | |
|
Interface files
data InterfaceFile Source #
readInterfaceFile :: forall m. MonadIO m => NameCacheAccessor m -> FilePath -> m (Either String InterfaceFile) Source #
Read a Haddock (.haddock
) interface file. Return either an
InterfaceFile
or an error message.
This function can be called in two ways. Within a GHC session it will update the use and update the session's name cache. Outside a GHC session a new empty name cache is used. The function is therefore generic in the monad being used. The exact monad is whichever monad the first argument, the getter and setter of the name cache, requires.
type NameCacheAccessor m = (m NameCache, NameCache -> m ()) Source #
Flags and options
Source-level options for controlling the documentation.
OptHide | This module should not appear in the docs. |
OptPrune | |
OptIgnoreExports | Pretend everything is exported. |
OptNotHome | Not the best place to get docs for things exported by this module. |
OptShowExtensions | Render enabled extensions for this module. |
Error handling
data HaddockException Source #
Haddock's own exception type.