-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A documentation-generation tool for Haskell libraries -- -- Haddock is a documentation-generation tool for Haskell libraries @package haddock @version 2.14.3 -- | The Haddock API: A rudimentory, highly experimental API exposing some -- of the internals of Haddock. Don't expect it to be stable. module Documentation.Haddock -- | 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. data Interface Interface :: !Module -> !FilePath -> !(HaddockModInfo Name) -> !(Documentation Name) -> !(Documentation DocName) -> ![DocOption] -> !(Map Name [LHsDecl Name]) -> !(DocMap Name) -> !(ArgMap Name) -> !(DocMap DocName) -> !(ArgMap DocName) -> !(Map Name [Name]) -> !(Map Name Fixity) -> ![ExportItem Name] -> ![ExportItem DocName] -> ![Name] -> ![Name] -> !AliasMap -> ![ClsInst] -> ![FamInst] -> !(Int, Int) -> !WarningMap -> Interface -- | The module behind this interface. ifaceMod :: Interface -> !Module -- | Original file name of the module. ifaceOrigFilename :: Interface -> !FilePath -- | Textual information about the module. ifaceInfo :: Interface -> !(HaddockModInfo Name) -- | Documentation header. ifaceDoc :: Interface -> !(Documentation Name) -- | Documentation header with cross-reference information. ifaceRnDoc :: Interface -> !(Documentation DocName) -- | Haddock options for this module (prune, ignore-exports, etc). ifaceOptions :: Interface -> ![DocOption] -- | 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. ifaceDeclMap :: Interface -> !(Map Name [LHsDecl Name]) -- | Documentation of declarations originating from the module (including -- subordinates). ifaceDocMap :: Interface -> !(DocMap Name) ifaceArgMap :: Interface -> !(ArgMap Name) -- | Documentation of declarations originating from the module (including -- subordinates). ifaceRnDocMap :: Interface -> !(DocMap DocName) ifaceRnArgMap :: Interface -> !(ArgMap DocName) ifaceSubMap :: Interface -> !(Map Name [Name]) ifaceFixMap :: Interface -> !(Map Name Fixity) ifaceExportItems :: Interface -> ![ExportItem Name] ifaceRnExportItems :: Interface -> ![ExportItem DocName] -- | All names exported by the module. ifaceExports :: Interface -> ![Name] -- | All "visible" names exported by the module. A visible name is a name -- that will show up in the documentation of the module. ifaceVisibleExports :: Interface -> ![Name] -- | Aliases of module imports as in import A.B.C as C. ifaceModuleAliases :: Interface -> !AliasMap -- | Instances exported by the module. ifaceInstances :: Interface -> ![ClsInst] ifaceFamInstances :: Interface -> ![FamInst] -- | The number of haddockable and haddocked items in the module, as a -- tuple. Haddockable items are the exports and the module itself. ifaceHaddockCoverage :: Interface -> !(Int, Int) -- | Warnings for things defined in this module. ifaceWarningMap :: Interface -> !WarningMap -- | A subset of the fields of Interface that we store in the -- interface files. data InstalledInterface InstalledInterface :: Module -> HaddockModInfo Name -> DocMap Name -> ArgMap Name -> [Name] -> [Name] -> [DocOption] -> Map Name [Name] -> Map Name Fixity -> InstalledInterface -- | The module represented by this interface. instMod :: InstalledInterface -> Module -- | Textual information about the module. instInfo :: InstalledInterface -> HaddockModInfo Name -- | Documentation of declarations originating from the module (including -- subordinates). instDocMap :: InstalledInterface -> DocMap Name instArgMap :: InstalledInterface -> ArgMap Name -- | All names exported by this module. instExports :: InstalledInterface -> [Name] -- | All "visible" names exported by the module. A visible name is a name -- that will show up in the documentation of the module. instVisibleExports :: InstalledInterface -> [Name] -- | Haddock options for this module (prune, ignore-exports, etc). instOptions :: InstalledInterface -> [DocOption] instSubMap :: InstalledInterface -> Map Name [Name] instFixMap :: InstalledInterface -> Map Name Fixity -- | 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. createInterfaces :: [Flag] -> [String] -> IO [Interface] -- | Create Interfaces and a link environment by typechecking the -- list of modules using the GHC API and processing the resulting syntax -- trees. processModules :: Verbosity -> [String] -> [Flag] -> [InterfaceFile] -> Ghc ([Interface], LinkEnv) data ExportItem name -- | An exported declaration. ExportDecl :: !(LHsDecl name) -> !(DocForDecl name) -> ![(name, DocForDecl name)] -> ![DocInstance name] -> ![(name, Fixity)] -> !Bool -> ExportItem name -- | A declaration. expItemDecl :: ExportItem name -> !(LHsDecl name) -- | Maybe a doc comment, and possibly docs for arguments (if this decl is -- a function or type-synonym). expItemMbDoc :: ExportItem name -> !(DocForDecl name) -- | Subordinate names, possibly with documentation. expItemSubDocs :: ExportItem name -> ![(name, DocForDecl name)] -- | Instances relevant to this declaration, possibly with documentation. expItemInstances :: ExportItem name -> ![DocInstance name] -- | Fixity decls relevant to this declaration (including subordinates). expItemFixities :: ExportItem name -> ![(name, Fixity)] -- | Whether the ExportItem is from a TH splice or not, for generating the -- appropriate type of Source link. expItemSpliced :: ExportItem name -> !Bool -- | An exported entity for which we have no documentation (perhaps because -- it resides in another package). ExportNoDecl :: !name -> ![name] -> ExportItem name expItemName :: ExportItem name -> !name -- | Subordinate names. expItemSubs :: ExportItem name -> ![name] -- | A section heading. ExportGroup :: !Int -> !String -> !(Doc name) -> ExportItem name -- | Section level (1, 2, 3, ...). expItemSectionLevel :: ExportItem name -> !Int -- | Section id (for hyperlinks). expItemSectionId :: ExportItem name -> !String -- | Section heading text. expItemSectionText :: ExportItem name -> !(Doc name) -- | Some documentation. ExportDoc :: !(Doc name) -> ExportItem name -- | A cross-reference to another module. ExportModule :: !Module -> ExportItem name type DocForDecl name = (Documentation name, FnArgsDoc name) -- | Arguments and result are indexed by Int, zero-based from the left, -- because that's the easiest to use when recursing over types. type FnArgsDoc name = Map Int (Doc name) -- | Type of environment used to cross-reference identifiers in the syntax. type LinkEnv = Map Name Module -- | Extends Name with cross-reference information. data DocName -- | This thing is part of the (existing or resulting) documentation. The -- Module is the preferred place in the documentation to refer to. Documented :: Name -> Module -> DocName -- | This thing is not part of the (existing or resulting) documentation, -- as far as Haddock knows. Undocumented :: Name -> DocName -- | An instance head that may have documentation. type DocInstance name = (InstHead name, Maybe (Doc name)) -- | The head of an instance. Consists of a class name, a list of kind -- parameters, a list of type parameters and an instance type type InstHead name = (name, [HsType name], [HsType name], InstType name) data Doc id DocEmpty :: Doc id DocAppend :: (Doc id) -> (Doc id) -> Doc id DocString :: String -> Doc id DocParagraph :: (Doc id) -> Doc id DocIdentifier :: id -> Doc id DocIdentifierUnchecked :: (ModuleName, OccName) -> Doc id DocModule :: String -> Doc id DocWarning :: (Doc id) -> Doc id DocEmphasis :: (Doc id) -> Doc id DocMonospaced :: (Doc id) -> Doc id DocBold :: (Doc id) -> Doc id DocUnorderedList :: [Doc id] -> Doc id DocOrderedList :: [Doc id] -> Doc id DocDefList :: [(Doc id, Doc id)] -> Doc id DocCodeBlock :: (Doc id) -> Doc id DocHyperlink :: Hyperlink -> Doc id DocPic :: Picture -> Doc id DocAName :: String -> Doc id DocProperty :: String -> Doc id DocExamples :: [Example] -> Doc id DocHeader :: (Header (Doc id)) -> Doc id data Example Example :: String -> [String] -> Example exampleExpression :: Example -> String exampleResult :: Example -> [String] data Hyperlink Hyperlink :: String -> Maybe String -> Hyperlink hyperlinkUrl :: Hyperlink -> String hyperlinkLabel :: Hyperlink -> Maybe String data DocMarkup id a Markup :: a -> (String -> a) -> (a -> a) -> (a -> a -> a) -> (id -> a) -> ((ModuleName, OccName) -> a) -> (String -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> (a -> a) -> ([a] -> a) -> ([a] -> a) -> ([(a, a)] -> a) -> (a -> a) -> (Hyperlink -> a) -> (String -> a) -> (Picture -> a) -> (String -> a) -> ([Example] -> a) -> (Header a -> a) -> DocMarkup id a markupEmpty :: DocMarkup id a -> a markupString :: DocMarkup id a -> String -> a markupParagraph :: DocMarkup id a -> a -> a markupAppend :: DocMarkup id a -> a -> a -> a markupIdentifier :: DocMarkup id a -> id -> a markupIdentifierUnchecked :: DocMarkup id a -> (ModuleName, OccName) -> a markupModule :: DocMarkup id a -> String -> a markupWarning :: DocMarkup id a -> a -> a markupEmphasis :: DocMarkup id a -> a -> a markupBold :: DocMarkup id a -> a -> a markupMonospaced :: DocMarkup id a -> a -> a markupUnorderedList :: DocMarkup id a -> [a] -> a markupOrderedList :: DocMarkup id a -> [a] -> a markupDefList :: DocMarkup id a -> [(a, a)] -> a markupCodeBlock :: DocMarkup id a -> a -> a markupHyperlink :: DocMarkup id a -> Hyperlink -> a markupAName :: DocMarkup id a -> String -> a markupPic :: DocMarkup id a -> Picture -> a markupProperty :: DocMarkup id a -> String -> a markupExample :: DocMarkup id a -> [Example] -> a markupHeader :: DocMarkup id a -> Header a -> a data Documentation name Documentation :: Maybe (Doc name) -> !(Maybe (Doc name)) -> Documentation name documentationDoc :: Documentation name -> Maybe (Doc name) documentationWarning :: Documentation name -> !(Maybe (Doc name)) type ArgMap a = Map Name (Map Int (Doc a)) type AliasMap = Map Module ModuleName type WarningMap = DocMap Name type DocMap a = Map Name (Doc a) data HaddockModInfo name HaddockModInfo :: Maybe (Doc name) -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> Maybe Language -> [ExtensionFlag] -> HaddockModInfo name hmi_description :: HaddockModInfo name -> Maybe (Doc name) hmi_copyright :: HaddockModInfo name -> Maybe String hmi_license :: HaddockModInfo name -> Maybe String hmi_maintainer :: HaddockModInfo name -> Maybe String hmi_stability :: HaddockModInfo name -> Maybe String hmi_portability :: HaddockModInfo name -> Maybe String hmi_safety :: HaddockModInfo name -> Maybe String hmi_language :: HaddockModInfo name -> Maybe Language hmi_extensions :: HaddockModInfo name -> [ExtensionFlag] markup :: DocMarkup id a -> Doc id -> a data InterfaceFile InterfaceFile :: LinkEnv -> [InstalledInterface] -> InterfaceFile ifLinkEnv :: InterfaceFile -> LinkEnv ifInstalledIfaces :: InterfaceFile -> [InstalledInterface] -- | 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. 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_BuiltInThemes :: Flag Flag_CSS :: String -> Flag Flag_ReadInterface :: String -> Flag Flag_DumpInterface :: String -> Flag Flag_Heading :: String -> Flag Flag_Html :: Flag Flag_Hoogle :: Flag Flag_Lib :: String -> Flag Flag_OutputDir :: FilePath -> Flag Flag_Prologue :: FilePath -> Flag Flag_SourceBaseURL :: String -> Flag Flag_SourceModuleURL :: String -> Flag Flag_SourceEntityURL :: String -> Flag Flag_SourceLEntityURL :: String -> Flag Flag_WikiBaseURL :: String -> Flag Flag_WikiModuleURL :: String -> Flag Flag_WikiEntityURL :: String -> Flag Flag_LaTeX :: Flag Flag_LaTeXStyle :: String -> Flag Flag_Help :: Flag Flag_Verbosity :: String -> Flag Flag_Version :: Flag Flag_CompatibleInterfaceVersions :: Flag Flag_InterfaceVersion :: Flag Flag_UseContents :: String -> Flag Flag_GenContents :: Flag Flag_UseIndex :: String -> Flag Flag_GenIndex :: Flag Flag_IgnoreAllExports :: Flag Flag_HideModule :: String -> Flag Flag_ShowExtensions :: String -> Flag Flag_OptGhc :: String -> Flag Flag_GhcLibDir :: String -> Flag Flag_GhcVersion :: Flag Flag_PrintGhcPath :: Flag Flag_PrintGhcLibDir :: Flag Flag_NoWarnings :: Flag Flag_UseUnicode :: Flag Flag_NoTmpCompDir :: Flag Flag_Qualification :: String -> Flag Flag_PrettyHtml :: Flag Flag_PrintMissingDocs :: Flag -- | Source-level options for controlling the documentation. data DocOption -- | This module should not appear in the docs. OptHide :: DocOption OptPrune :: DocOption -- | Pretend everything is exported. OptIgnoreExports :: DocOption -- | Not the best place to get docs for things exported by this module. OptNotHome :: DocOption -- | Render enabled extensions for this module. OptShowExtensions :: DocOption -- | Run Haddock with given list of arguments. -- -- Haddock's own main function is defined in terms of this: -- --
--   main = getArgs >>= haddock
--   
haddock :: [String] -> IO ()