haddock-api-2.24.2: A documentation-generation tool for Haskell libraries
Copyright(c) David Waern 2010
LicenseBSD-like
Maintainerhaddock@projects.haskellorg
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Documentation.Haddock

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

data InstalledInterface Source #

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

Constructors

InstalledInterface 

Fields

createInterfaces Source #

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.

processModules Source #

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

ExportNoDecl

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

Fields

ExportGroup

A section heading.

Fields

ExportDoc !(MDoc (IdP 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.

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

Instances details
Eq DocName Source # 
Instance details

Defined in Haddock.Types

Methods

(==) :: DocName -> DocName -> Bool #

(/=) :: DocName -> DocName -> Bool #

Data DocName Source # 
Instance details

Defined in Haddock.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DocName -> c DocName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DocName #

toConstr :: DocName -> Constr #

dataTypeOf :: DocName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DocName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DocName) #

gmapT :: (forall b. Data b => b -> b) -> DocName -> DocName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DocName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DocName -> r #

gmapQ :: (forall d. Data d => d -> u) -> DocName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DocName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DocName -> m DocName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DocName -> m DocName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DocName -> m DocName #

NamedThing DocName Source # 
Instance details

Defined in Haddock.Types

HasOccName DocName Source # 
Instance details

Defined in Haddock.Types

Methods

occName :: DocName -> OccName #

Binary DocName Source # 
Instance details

Defined in Haddock.InterfaceFile

Outputable DocName Source #

Useful for debugging

Instance details

Defined in Haddock.Types

Methods

ppr :: DocName -> SDoc #

pprPrec :: Rational -> DocName -> SDoc #

OutputableBndr DocName Source # 
Instance details

Defined in Haddock.Types

Instances

type DocInstance name = (InstHead name, Maybe (MDoc (IdP name)), Located (IdP name), Maybe Module) Source #

An instance head that may have documentation and a source location.

data InstHead name Source #

The head of an instance. Consists of a class name, a list of type parameters (which may be annotated with kinds), and an instance type

Documentation comments

type Doc id = DocH (Wrap (ModuleName, OccName)) (Wrap id) Source #

type MDoc id = MetaDoc (Wrap (ModuleName, OccName)) (Wrap id) Source #

data DocH mod id #

Constructors

DocEmpty 
DocAppend (DocH mod id) (DocH mod id) 
DocString String 
DocParagraph (DocH mod id) 
DocIdentifier id 
DocIdentifierUnchecked mod

A qualified identifier that couldn't be resolved.

DocModule (ModLink (DocH mod id))

A link to a module, with an optional label.

DocWarning (DocH mod id)

This constructor has no counterpart in Haddock markup.

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 (DocH mod id)) 
DocPic Picture 
DocMathInline String 
DocMathDisplay String 
DocAName String

A (HTML) anchor. It must not contain any spaces.

DocProperty String 
DocExamples [Example] 
DocHeader (Header (DocH mod id)) 
DocTable (Table (DocH mod id)) 

Instances

Instances details
Bitraversable DocH

NOTE: Only defined for base >= 4.10.0

Instance details

Defined in Documentation.Haddock.Types

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> DocH a b -> f (DocH c d) #

Bifoldable DocH

NOTE: Only defined for base >= 4.10.0

Instance details

Defined in Documentation.Haddock.Types

Methods

bifold :: Monoid m => DocH m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> DocH a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> DocH a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> DocH a b -> c #

Bifunctor DocH

NOTE: Only defined for base >= 4.8.0

Instance details

Defined in Documentation.Haddock.Types

Methods

bimap :: (a -> b) -> (c -> d) -> DocH a c -> DocH b d #

first :: (a -> b) -> DocH a c -> DocH b c #

second :: (b -> c) -> DocH a b -> DocH a c #

Functor (DocH mod) 
Instance details

Defined in Documentation.Haddock.Types

Methods

fmap :: (a -> b) -> DocH mod a -> DocH mod b #

(<$) :: a -> DocH mod b -> DocH mod a #

Foldable (DocH mod) 
Instance details

Defined in Documentation.Haddock.Types

Methods

fold :: Monoid m => DocH mod m -> m #

foldMap :: Monoid m => (a -> m) -> DocH mod a -> m #

foldMap' :: Monoid m => (a -> m) -> DocH mod a -> m #

foldr :: (a -> b -> b) -> b -> DocH mod a -> b #

foldr' :: (a -> b -> b) -> b -> DocH mod a -> b #

foldl :: (b -> a -> b) -> b -> DocH mod a -> b #

foldl' :: (b -> a -> b) -> b -> DocH mod a -> b #

foldr1 :: (a -> a -> a) -> DocH mod a -> a #

foldl1 :: (a -> a -> a) -> DocH mod a -> a #

toList :: DocH mod a -> [a] #

null :: DocH mod a -> Bool #

length :: DocH mod a -> Int #

elem :: Eq a => a -> DocH mod a -> Bool #

maximum :: Ord a => DocH mod a -> a #

minimum :: Ord a => DocH mod a -> a #

sum :: Num a => DocH mod a -> a #

product :: Num a => DocH mod a -> a #

Traversable (DocH mod) 
Instance details

Defined in Documentation.Haddock.Types

Methods

traverse :: Applicative f => (a -> f b) -> DocH mod a -> f (DocH mod b) #

sequenceA :: Applicative f => DocH mod (f a) -> f (DocH mod a) #

mapM :: Monad m => (a -> m b) -> DocH mod a -> m (DocH mod b) #

sequence :: Monad m => DocH mod (m a) -> m (DocH mod a) #

(Eq id, Eq mod) => Eq (DocH mod id) 
Instance details

Defined in Documentation.Haddock.Types

Methods

(==) :: DocH mod id -> DocH mod id -> Bool #

(/=) :: DocH mod id -> DocH mod id -> Bool #

(Show id, Show mod) => Show (DocH mod id) 
Instance details

Defined in Documentation.Haddock.Types

Methods

showsPrec :: Int -> DocH mod id -> ShowS #

show :: DocH mod id -> String #

showList :: [DocH mod id] -> ShowS #

(NFData a, NFData mod) => NFData (DocH mod a) Source # 
Instance details

Defined in Haddock.Types

Methods

rnf :: DocH mod a -> () #

(Binary mod, Binary id) => Binary (DocH mod id) Source # 
Instance details

Defined in Haddock.InterfaceFile

Methods

put_ :: BinHandle -> DocH mod id -> IO () #

put :: BinHandle -> DocH mod id -> IO (Bin (DocH mod id)) #

get :: BinHandle -> IO (DocH mod id) #

data Example #

Constructors

Example 

Instances

Instances details
Eq Example 
Instance details

Defined in Documentation.Haddock.Types

Methods

(==) :: Example -> Example -> Bool #

(/=) :: Example -> Example -> Bool #

Show Example 
Instance details

Defined in Documentation.Haddock.Types

NFData Example Source # 
Instance details

Defined in Haddock.Types

Methods

rnf :: Example -> () #

Binary Example Source # 
Instance details

Defined in Haddock.InterfaceFile

data Hyperlink id #

Constructors

Hyperlink 

Instances

type DocMarkup id a = DocMarkupH (Wrap (ModuleName, OccName)) id a Source #

data DocMarkupH mod id a #

DocMarkupH is a set of instructions for marking up documentation. In fact, it's really just a mapping from Doc to some other type [a], where [a] is usually the type of the output (HTML, say). Use markup to apply a DocMarkupH to a DocH.

Since: haddock-library-1.4.5

Constructors

Markup 

Fields

data Documentation name Source #

Constructors

Documentation 

Fields

Instances

Instances details
Functor Documentation Source # 
Instance details

Defined in Haddock.Types

Methods

fmap :: (a -> b) -> Documentation a -> Documentation b #

(<$) :: a -> Documentation b -> Documentation a #

type ArgMap a = Map Name (Map Int (MDoc a)) Source #

type DocMap a = Map Name (MDoc a) Source #

markup :: DocMarkupH mod id a -> DocH mod id -> a #

Interface files

readInterfaceFile Source #

Arguments

:: forall m. MonadIO m 
=> NameCacheAccessor m 
-> FilePath 
-> Bool

Disable version check. Can cause runtime crash.

-> m (Either String InterfaceFile) 

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 Flag Source #

Instances

Instances details
Eq Flag Source # 
Instance details

Defined in Haddock.Options

Methods

(==) :: Flag -> Flag -> Bool #

(/=) :: Flag -> Flag -> Bool #

Show Flag Source # 
Instance details

Defined in Haddock.Options

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

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.

OptShowExtensions

Render enabled extensions for this module.

Instances

Instances details
Eq DocOption Source # 
Instance details

Defined in Haddock.Types

Show DocOption Source # 
Instance details

Defined in Haddock.Types

Binary DocOption Source # 
Instance details

Defined in Haddock.InterfaceFile

Error handling

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

haddockWithGhc :: (forall a. [Flag] -> Ghc a -> IO a) -> [String] -> IO () Source #

getGhcDirs :: [Flag] -> IO (Maybe FilePath, Maybe FilePath) Source #

Find the lib directory for GHC and the path to ghc

withGhc :: [Flag] -> Ghc a -> IO a Source #