Skip to content
Snippets Groups Projects
Commit d4f600a5 authored by David Waern's avatar David Waern
Browse files

Fix layout problems in Haddock.Types

parent 7648b30c
No related branches found
No related tags found
No related merge requests found
...@@ -6,13 +6,15 @@ ...@@ -6,13 +6,15 @@
-- Ported to use the GHC API by David Waern 2006 -- Ported to use the GHC API by David Waern 2006
-- --
module Haddock.Types where module Haddock.Types where
import GHC hiding (NoLink) import GHC hiding (NoLink)
import Outputable import Outputable
import Data.Map import Data.Map
data DocOption data DocOption
= OptHide -- ^ This module should not appear in the docs = OptHide -- ^ This module should not appear in the docs
| OptPrune | OptPrune
...@@ -21,11 +23,12 @@ data DocOption ...@@ -21,11 +23,12 @@ data DocOption
-- exported by this module. -- exported by this module.
deriving (Eq, Show) deriving (Eq, Show)
data ExportItem name data ExportItem name
= ExportDecl { = ExportDecl {
-- | The original name -- | The original name
expItemName :: Name, expItemName :: Name,
-- | A declaration -- | A declaration
...@@ -34,13 +37,13 @@ data ExportItem name ...@@ -34,13 +37,13 @@ data ExportItem name
-- | Maybe a doc comment -- | Maybe a doc comment
expItemMbDoc :: Maybe (HsDoc name), expItemMbDoc :: Maybe (HsDoc name),
-- | Instances relevant to this declaration -- | Instances relevant to this declaration
expItemInstances :: [InstHead name] expItemInstances :: [InstHead name]
} -- ^ An exported declaration } -- ^ An exported declaration
| ExportNoDecl { | ExportNoDecl {
-- | The original name -- | The original name
expItemName :: Name, expItemName :: Name,
-- | Where to link to -- | Where to link to
...@@ -50,8 +53,8 @@ data ExportItem name ...@@ -50,8 +53,8 @@ data ExportItem name
expItemSubs :: [name] expItemSubs :: [name]
} -- ^ An exported entity for which we have no } -- ^ An exported entity for which we have no
-- documentation (perhaps because it resides in -- documentation (perhaps because it resides in
-- another package) -- another package)
| ExportGroup { | ExportGroup {
...@@ -59,10 +62,10 @@ data ExportItem name ...@@ -59,10 +62,10 @@ data ExportItem name
expItemSectionLevel :: Int, expItemSectionLevel :: Int,
-- | Section id (for hyperlinks) -- | Section id (for hyperlinks)
expItemSectionId :: String, expItemSectionId :: String,
-- | Section heading text -- | Section heading text
expItemSectionText :: HsDoc name expItemSectionText :: HsDoc name
} -- ^ A section heading } -- ^ A section heading
...@@ -70,17 +73,21 @@ data ExportItem name ...@@ -70,17 +73,21 @@ data ExportItem name
| ExportModule Module -- ^ A cross-reference to another module | ExportModule Module -- ^ A cross-reference to another module
type InstHead name = ([HsPred name], name, [HsType name]) type InstHead name = ([HsPred name], name, [HsType name])
type ModuleMap = Map Module HaddockModule type ModuleMap = Map Module HaddockModule
type DocMap = Map Name (HsDoc DocName) type DocMap = Map Name (HsDoc DocName)
type DocEnv = Map Name Name type DocEnv = Map Name Name
data DocName = Link Name | NoLink Name data DocName = Link Name | NoLink Name
instance Outputable DocName where instance Outputable DocName where
ppr (Link n) = ppr n ppr (Link n) = ppr n
ppr (NoLink n) = ppr n ppr (NoLink n) = ppr n
data HaddockModule = HM { data HaddockModule = HM {
-- | A value to identify the module -- | A value to identify the module
...@@ -129,6 +136,7 @@ data HaddockModule = HM { ...@@ -129,6 +136,7 @@ data HaddockModule = HM {
hmod_instances :: [Instance] hmod_instances :: [Instance]
} }
data DocMarkup id a = Markup { data DocMarkup id a = Markup {
markupEmpty :: a, markupEmpty :: a,
markupString :: String -> a, markupString :: String -> a,
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment