haddock-2.13.2.1: A documentation-generation tool for Haskell libraries

Portabilityportable
Stabilityexperimental
Maintainerhaddock@projects.haskellorg
Safe HaskellNone

Documentation.Haddock

Contents

Description

The Haddock API: A rudimentory, highly experimental API exposing some of the internals of Haddock. Don't expect it to be stable.

Synopsis

Interface

data Interface Source

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.

Constructors

Interface 

Fields

ifaceMod :: !Module

The module behind this interface.

ifaceOrigFilename :: !FilePath

Original file name of the module.

ifaceInfo :: !(HaddockModInfo Name)

Textual information about the module.

ifaceDoc :: !(Documentation Name)

Documentation header.

ifaceRnDoc :: !(Documentation DocName)

Documentation header with cross-reference information.

ifaceOptions :: ![DocOption]

Haddock options for this module (prune, ignore-exports, etc).

ifaceDeclMap :: !(Map Name [LHsDecl Name])

Declarations originating from the module. Excludes declarations without names (instances and stand-alone documentation comments). Includes names of subordinate declarations mapped to their parent declarations.

ifaceDocMap :: !(DocMap Name)

Documentation of declarations originating from the module (including subordinates).

ifaceArgMap :: !(ArgMap Name)
 
ifaceRnDocMap :: !(DocMap DocName)

Documentation of declarations originating from the module (including subordinates).

ifaceRnArgMap :: !(ArgMap DocName)
 
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.

ifaceModuleAliases :: !AliasMap

Aliases of module imports as in import A.B.C as C.

ifaceInstances :: ![ClsInst]

Instances exported by the module.

ifaceHaddockCoverage :: !(Int, Int)

The number of haddockable and haddocked items in the module, as a tuple. Haddockable items are the exports and the module itself.

ifaceWarningMap :: !WarningMap

Warnings for things defined in this module.

data InstalledInterface Source

A subset of the fields of Interface that we store in the interface files.

Constructors

InstalledInterface 

Fields

instMod :: Module

The module represented by this interface.

instInfo :: HaddockModInfo Name

Textual information about the module.

instDocMap :: DocMap Name

Documentation of declarations originating from the module (including subordinates).

instArgMap :: ArgMap Name
 
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]
 

createInterfacesSource

Arguments

:: [Flag]

A list of command-line flags

-> [String]

File or module names

-> IO [Interface]

Resulting list of interfaces

Create Interface structures from a given list of Haddock command-line flags and file or module names (as accepted by haddock executable). Flags that control documentation generation or show help or version information are ignored.

processModulesSource

Arguments

:: Verbosity

Verbosity 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 Interfaces 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

Constructors

ExportDecl

An exported declaration.

Fields

expItemDecl :: !(LHsDecl name)

A declaration.

expItemMbDoc :: !(DocForDecl name)

Maybe 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.

ExportNoDecl

An exported entity for which we have no documentation (perhaps because it resides in another package).

Fields

expItemName :: !name
 
expItemSubs :: ![name]

Subordinate names.

ExportGroup

A section heading.

Fields

expItemSectionLevel :: !Int

Section level (1, 2, 3, ...).

expItemSectionId :: !String

Section id (for hyperlinks).

expItemSectionText :: !(Doc name)

Section heading text.

ExportDoc !(Doc name)

Some documentation.

ExportModule !Module

A cross-reference to another module.

type DocForDecl name = (Documentation 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.

Cross-referencing

type LinkEnv = Map Name ModuleSource

Type of environment used to cross-reference identifiers in the syntax.

data DocName Source

Extends Name with cross-reference information.

Constructors

Documented Name Module

This thing is part of the (existing or resulting) documentation. The Module is the preferred place in the documentation to refer to.

Undocumented Name

This thing is not part of the (existing or resulting) documentation, as far as Haddock knows.

Instances

type DocInstance name = (InstHead name, Maybe (Doc name))Source

An instance head that may have documentation.

type InstHead name = ([HsType 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 DocMarkup id a Source

Constructors

Markup 

Fields

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
 
markupMonospaced :: a -> a
 
markupUnorderedList :: [a] -> a
 
markupOrderedList :: [a] -> a
 
markupDefList :: [(a, a)] -> a
 
markupCodeBlock :: a -> a
 
markupHyperlink :: Hyperlink -> a
 
markupAName :: String -> a
 
markupPic :: String -> a
 
markupProperty :: String -> a
 
markupExample :: [Example] -> a
 

data Documentation name Source

Constructors

Documentation 

Fields

documentationDoc :: Maybe (Doc name)
 
documentationWarning :: !(Maybe (Doc name))
 

type ArgMap a = Map Name (Map Int (Doc a))Source

type DocMap a = Map Name (Doc a)Source

markup :: DocMarkup id a -> Doc id -> aSource

Interface files

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.

Flags and options

data DocOption Source

Source-level options for controlling the documentation.

Constructors

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.

Program entry point

haddock :: [String] -> IO ()Source

Run Haddock with given list of arguments.

Haddock's own main function is defined in terms of this:

 main = getArgs >>= haddock