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

Portabilityportable
Stabilityexperimental
Maintainerhaddock@projects.haskellorg

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

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 

Fields

ifaceMod :: Module

The module represented by this interface.

ifaceOrigFilename :: FilePath

Original 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 DeclInfo

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.

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 

Fields

instMod :: Module

The module represented by this interface.

instInfo :: HaddockModInfo Name

Textual 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]
 

createInterfacesSource

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

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

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

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 

Fields

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
 

Interface files

(.haddock files)

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.

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.