haddock-2.7.0: A documentation-generation tool for Haskell librariesSource codeContentsIndex
Documentation.Haddock
Portabilityportable
Stabilityexperimental
Maintainerhaddock@projects.haskellorg
Contents
Interface
Export items & declarations
Hyperlinking
Instances
Documentation comments
Interface files
Flags and options
Description
The Haddock API: A rudimentory, highly experimental API exposing some of the internals of Haddock. Don't expect it to be stable.
Synopsis
data Interface = Interface {
ifaceMod :: Module
ifaceOrigFilename :: FilePath
ifaceInfo :: !(HaddockModInfo Name)
ifaceDoc :: !(Maybe (Doc Name))
ifaceRnDoc :: Maybe (Doc DocName)
ifaceOptions :: ![DocOption]
ifaceDeclMap :: Map Name DeclInfo
ifaceRnDocMap :: Map Name (DocForDecl DocName)
ifaceSubMap :: Map Name [Name]
ifaceExportItems :: ![ExportItem Name]
ifaceRnExportItems :: [ExportItem DocName]
ifaceExports :: ![Name]
ifaceVisibleExports :: ![Name]
ifaceInstances :: ![Instance]
ifaceInstanceDocMap :: Map Name (Doc Name)
}
data InstalledInterface = InstalledInterface {
instMod :: Module
instInfo :: HaddockModInfo Name
instDocMap :: Map Name (DocForDecl Name)
instExports :: [Name]
instVisibleExports :: [Name]
instOptions :: [DocOption]
instSubMap :: Map Name [Name]
}
createInterfaces :: Verbosity -> [String] -> [Flag] -> [InterfaceFile] -> Ghc ([Interface], LinkEnv)
data ExportItem name
= ExportDecl {
expItemDecl :: LHsDecl name
expItemMbDoc :: DocForDecl name
expItemSubDocs :: [(name, DocForDecl name)]
expItemInstances :: [DocInstance name]
}
| ExportNoDecl {
expItemName :: name
expItemSubs :: [name]
}
| ExportGroup {
expItemSectionLevel :: Int
expItemSectionId :: String
expItemSectionText :: Doc name
}
| ExportDoc (Doc name)
| ExportModule Module
type DeclInfo = (Decl, DocForDecl Name, [(Name, DocForDecl Name)])
type DocForDecl name = (Maybe (Doc name), FnArgsDoc name)
type FnArgsDoc name = Map Int (Doc name)
type LinkEnv = Map Name Module
data DocName
= Documented Name Module
| Undocumented Name
docNameOcc :: DocName -> OccName
type DocInstance name = (InstHead name, Maybe (Doc name))
type InstHead name = ([HsPred name], name, [HsType name])
data Doc id
= DocEmpty
| DocAppend (Doc id) (Doc id)
| DocString String
| DocParagraph (Doc id)
| DocIdentifier [id]
| DocModule String
| DocEmphasis (Doc id)
| DocMonospaced (Doc id)
| DocUnorderedList [Doc id]
| DocOrderedList [Doc id]
| DocDefList [(Doc id, Doc id)]
| DocCodeBlock (Doc id)
| DocURL String
| DocPic String
| DocAName String
data DocMarkup id a = Markup {
markupEmpty :: a
markupString :: String -> a
markupParagraph :: a -> a
markupAppend :: a -> a -> a
markupIdentifier :: [id] -> a
markupModule :: String -> a
markupEmphasis :: a -> a
markupMonospaced :: a -> a
markupUnorderedList :: [a] -> a
markupOrderedList :: [a] -> a
markupDefList :: [(a, a)] -> a
markupCodeBlock :: a -> a
markupURL :: String -> a
markupAName :: String -> a
markupPic :: String -> a
}
data HaddockModInfo name = HaddockModInfo {
hmi_description :: Maybe (Doc name)
hmi_portability :: Maybe String
hmi_stability :: Maybe String
hmi_maintainer :: Maybe String
}
data InterfaceFile = InterfaceFile {
ifLinkEnv :: LinkEnv
ifInstalledIfaces :: [InstalledInterface]
}
readInterfaceFile :: 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_CSS String
| Flag_Debug
| Flag_ReadInterface String
| Flag_DumpInterface String
| Flag_Heading String
| Flag_Html
| Flag_Hoogle
| Flag_HtmlHelp String
| Flag_Lib String
| Flag_OutputDir FilePath
| Flag_Prologue FilePath
| Flag_SourceBaseURL String
| Flag_SourceModuleURL String
| Flag_SourceEntityURL String
| Flag_WikiBaseURL String
| Flag_WikiModuleURL String
| Flag_WikiEntityURL String
| Flag_Help
| Flag_Verbosity String
| Flag_Version
| Flag_UseContents String
| Flag_GenContents
| Flag_UseIndex String
| Flag_GenIndex
| Flag_IgnoreAllExports
| Flag_HideModule String
| Flag_OptGhc String
| Flag_GhcLibDir String
| Flag_GhcVersion
| Flag_PrintGhcLibDir
| Flag_NoWarnings
| Flag_UseUnicode
data DocOption
= OptHide
| OptPrune
| OptIgnoreExports
| OptNotHome
Interface
data Interface Source
The data structure used to render a Haddock page for a module - it is the interface of the module. The core of Haddock lies in creating this structure (see Haddock.Interface). The structure also holds intermediate data needed during its creation.
Constructors
Interface
ifaceMod :: ModuleThe module represented by this interface.
ifaceOrigFilename :: FilePathOriginal file name of the module.
ifaceInfo :: !(HaddockModInfo Name)Textual information about the module.
ifaceDoc :: !(Maybe (Doc Name))Documentation header.
ifaceRnDoc :: Maybe (Doc DocName)Documentation header with link information.
ifaceOptions :: ![DocOption]Haddock options for this module (prune, ignore-exports, etc).
ifaceDeclMap :: Map Name DeclInfoDeclarations originating from the module. Excludes declarations without names (instances and stand-alone documentation comments). Includes names of subordinate declarations mapped to their parent declarations.
ifaceRnDocMap :: Map Name (DocForDecl DocName)Documentation of declarations originating from the module (including subordinates).
ifaceSubMap :: Map Name [Name]
ifaceExportItems :: ![ExportItem Name]
ifaceRnExportItems :: [ExportItem DocName]
ifaceExports :: ![Name]All names exported by the module.
ifaceVisibleExports :: ![Name]All "visible" names exported by the module. A visible name is a name that will show up in the documentation of the module.
ifaceInstances :: ![Instance]Instances exported by the module.
ifaceInstanceDocMap :: Map Name (Doc Name)Documentation of instances defined in the module.
data InstalledInterface Source
A smaller version of Interface that can be created from Haddock's interface files (InterfaceFile).
Constructors
InstalledInterface
instMod :: ModuleThe module represented by this interface.
instInfo :: HaddockModInfo NameTextual information about the module.
instDocMap :: Map Name (DocForDecl Name)Documentation of declarations originating from the module (including subordinates).
instExports :: [Name]All names exported by this module.
instVisibleExports :: [Name]All "visible" names exported by the module. A visible name is a name that will show up in the documentation of the module.
instOptions :: [DocOption]Haddock options for this module (prune, ignore-exports, etc).
instSubMap :: Map Name [Name]
show/hide Instances
createInterfacesSource
:: VerbosityVerbosity of logging to stdout
-> [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 structures by typechecking the list of modules using the GHC API and processing the resulting syntax trees.
Export items & declarations
data ExportItem name Source
Constructors
ExportDeclAn exported declaration
expItemDecl :: LHsDecl nameA declaration
expItemMbDoc :: DocForDecl nameMaybe a doc comment, and possibly docs for arguments (if this decl is a function or type-synonym)
expItemSubDocs :: [(name, DocForDecl name)]Subordinate names, possibly with documentation
expItemInstances :: [DocInstance name]Instances relevant to this declaration, possibly with documentation
ExportNoDeclAn exported entity for which we have no documentation (perhaps because it resides in another package)
expItemName :: name
expItemSubs :: [name]Subordinate names
ExportGroupA section heading
expItemSectionLevel :: IntSection level (1, 2, 3, ... )
expItemSectionId :: StringSection id (for hyperlinks)
expItemSectionText :: Doc nameSection heading text
ExportDoc (Doc name)Some documentation
ExportModule ModuleA cross-reference to another module
type DeclInfo = (Decl, DocForDecl Name, [(Name, DocForDecl Name)])Source
A declaration that may have documentation, including its subordinates, which may also have documentation
type DocForDecl name = (Maybe (Doc name), FnArgsDoc name)Source
type FnArgsDoc name = Map Int (Doc 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.
Hyperlinking
type LinkEnv = Map Name ModuleSource
An environment used to create hyper-linked syntax.
data DocName Source
An extension of Name that may contain the preferred place to link to in the documentation.
Constructors
Documented Name Module
Undocumented Name
show/hide Instances
docNameOcc :: DocName -> OccNameSource
The OccName of this name.
Instances
type DocInstance name = (InstHead name, Maybe (Doc name))Source
An instance head that may have documentation.
type InstHead name = ([HsPred name], name, [HsType name])Source
The head of an instance. Consists of a context, a class name and a list of instance types.
Documentation comments
data Doc id Source
Constructors
DocEmpty
DocAppend (Doc id) (Doc id)
DocString String
DocParagraph (Doc id)
DocIdentifier [id]
DocModule String
DocEmphasis (Doc id)
DocMonospaced (Doc id)
DocUnorderedList [Doc id]
DocOrderedList [Doc id]
DocDefList [(Doc id, Doc id)]
DocCodeBlock (Doc id)
DocURL String
DocPic String
DocAName String
show/hide Instances
Functor Doc
Eq id => Eq (Doc id)
Show id => Show (Doc id)
Binary id => Binary (Doc id)
data DocMarkup id a Source
Constructors
Markup
markupEmpty :: a
markupString :: String -> a
markupParagraph :: a -> a
markupAppend :: a -> a -> a
markupIdentifier :: [id] -> a
markupModule :: String -> a
markupEmphasis :: a -> a
markupMonospaced :: a -> a
markupUnorderedList :: [a] -> a
markupOrderedList :: [a] -> a
markupDefList :: [(a, a)] -> a
markupCodeBlock :: a -> a
markupURL :: String -> a
markupAName :: String -> a
markupPic :: String -> a
data HaddockModInfo name Source
Constructors
HaddockModInfo
hmi_description :: Maybe (Doc name)
hmi_portability :: Maybe String
hmi_stability :: Maybe String
hmi_maintainer :: Maybe String
show/hide Instances
Interface files
(.haddock files)
data InterfaceFile Source
Constructors
InterfaceFile
ifLinkEnv :: LinkEnv
ifInstalledIfaces :: [InstalledInterface]
show/hide Instances
readInterfaceFile :: 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.

nameCacheFromGhc :: NameCacheAccessor GhcSource
freshNameCache :: NameCacheAccessor IOSource
type NameCacheAccessor m = (m NameCache, NameCache -> m ())Source
Flags and options
data Flag Source
Constructors
Flag_CSS String
Flag_Debug
Flag_ReadInterface String
Flag_DumpInterface String
Flag_Heading String
Flag_Html
Flag_Hoogle
Flag_HtmlHelp String
Flag_Lib String
Flag_OutputDir FilePath
Flag_Prologue FilePath
Flag_SourceBaseURL String
Flag_SourceModuleURL String
Flag_SourceEntityURL String
Flag_WikiBaseURL String
Flag_WikiModuleURL String
Flag_WikiEntityURL String
Flag_Help
Flag_Verbosity String
Flag_Version
Flag_UseContents String
Flag_GenContents
Flag_UseIndex String
Flag_GenIndex
Flag_IgnoreAllExports
Flag_HideModule String
Flag_OptGhc String
Flag_GhcLibDir String
Flag_GhcVersion
Flag_PrintGhcLibDir
Flag_NoWarnings
Flag_UseUnicode
show/hide Instances
data DocOption Source
Source-level options for controlling the documentation.
Constructors
OptHideThis module should not appear in the docs
OptPrune
OptIgnoreExportsPretend everything is exported
OptNotHomeNot the best place to get docs for things exported by this module.
show/hide Instances
Produced by Haddock version 2.6.0