haddock-api-2.17.3: A documentation-generation tool for Haskell libraries

Copyright(c) David Waern 2010
LicenseBSD-like
Maintainerhaddock@projects.haskellorg
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

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

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

Eq DocName Source # 

Methods

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

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

Data DocName Source # 

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 :: (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 # 
Outputable DocName Source #

Useful for debugging

Methods

ppr :: DocName -> SDoc #

pprPrec :: Rational -> DocName -> SDoc #

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.

data InstHead name Source #

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 Doc id = DocH (ModuleName, OccName) id Source #

data DocH mod id :: * -> * -> * #

Instances

Functor (DocH mod) 

Methods

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

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

Foldable (DocH mod) 

Methods

fold :: Monoid m => DocH mod m -> 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) 

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 mod, Eq id) => Eq (DocH mod id) 

Methods

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

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

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

Methods

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

show :: DocH mod id -> String #

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

data Example :: * #

Constructors

Example 

Instances

data DocMarkup id a Source #

Constructors

Markup 

Fields

data Documentation name Source #

Constructors

Documentation 

Fields

Instances

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

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

markup :: DocMarkup id a -> Doc id -> a Source #

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.

OptShowExtensions

Render enabled extensions for this module.

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 #

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