PageRenderTime 49ms CodeModel.GetById 20ms RepoModel.GetById 0ms app.codeStats 0ms

/ghc-7.0.4/utils/haddock/src/Haddock/Types.hs

http://picorec.googlecode.com/
Haskell | 440 lines | 194 code | 121 blank | 125 comment | 0 complexity | 3e29082517678cd3688c865431d45c3e MD5 | raw file
Possible License(s): BSD-3-Clause, BSD-2-Clause
  1. {-# OPTIONS_HADDOCK hide #-}
  2. {-# LANGUAGE DeriveDataTypeable, DeriveFunctor #-}
  3. -----------------------------------------------------------------------------
  4. -- |
  5. -- Module : Haddock.Types
  6. -- Copyright : (c) Simon Marlow 2003-2006,
  7. -- David Waern 2006-2009
  8. -- License : BSD-like
  9. --
  10. -- Maintainer : haddock@projects.haskellorg
  11. -- Stability : experimental
  12. -- Portability : portable
  13. --
  14. -- Types that are commonly used through-out Haddock. Some of the most
  15. -- important types are defined here, like 'Interface' and 'DocName'.
  16. -----------------------------------------------------------------------------
  17. module Haddock.Types (
  18. module Haddock.Types
  19. , HsDocString, LHsDocString
  20. ) where
  21. import Control.Exception
  22. import Control.Arrow
  23. import Data.Typeable
  24. import Data.Map (Map)
  25. import qualified Data.Map as Map
  26. import GHC hiding (NoLink)
  27. import Name
  28. -----------------------------------------------------------------------------
  29. -- * Convenient synonyms
  30. -----------------------------------------------------------------------------
  31. type IfaceMap = Map Module Interface
  32. type InstIfaceMap = Map Module InstalledInterface
  33. type DocMap = Map Name (Doc DocName)
  34. type SrcMap = Map PackageId FilePath
  35. type Decl = LHsDecl Name
  36. type GhcDocHdr = Maybe LHsDocString
  37. type DocPaths = (FilePath, Maybe FilePath) -- paths to HTML and sources
  38. -----------------------------------------------------------------------------
  39. -- * Interface
  40. -----------------------------------------------------------------------------
  41. -- | 'Interface' holds all information used to render a single Haddock page.
  42. -- It represents the /interface/ of a module. The core business of Haddock
  43. -- lies in creating this structure. Note that the record contains some fields
  44. -- that are only used to create the final record, and that are not used by the
  45. -- backends.
  46. data Interface = Interface
  47. {
  48. -- | The module behind this interface.
  49. ifaceMod :: Module
  50. -- | Original file name of the module.
  51. , ifaceOrigFilename :: FilePath
  52. -- | Textual information about the module.
  53. , ifaceInfo :: !(HaddockModInfo Name)
  54. -- | Documentation header.
  55. , ifaceDoc :: !(Maybe (Doc Name))
  56. -- | Documentation header with cross-reference information.
  57. , ifaceRnDoc :: Maybe (Doc DocName)
  58. -- | Haddock options for this module (prune, ignore-exports, etc).
  59. , ifaceOptions :: ![DocOption]
  60. -- | Declarations originating from the module. Excludes declarations without
  61. -- names (instances and stand-alone documentation comments). Includes
  62. -- names of subordinate declarations mapped to their parent declarations.
  63. , ifaceDeclMap :: Map Name DeclInfo
  64. -- | Documentation of declarations originating from the module (including
  65. -- subordinates).
  66. , ifaceRnDocMap :: Map Name (DocForDecl DocName)
  67. , ifaceSubMap :: Map Name [Name]
  68. , ifaceExportItems :: ![ExportItem Name]
  69. , ifaceRnExportItems :: [ExportItem DocName]
  70. -- | All names exported by the module.
  71. , ifaceExports :: ![Name]
  72. -- | All \"visible\" names exported by the module.
  73. -- A visible name is a name that will show up in the documentation of the
  74. -- module.
  75. , ifaceVisibleExports :: ![Name]
  76. -- | Instances exported by the module.
  77. , ifaceInstances :: ![Instance]
  78. -- | Documentation of instances defined in the module.
  79. , ifaceInstanceDocMap :: Map Name (Doc Name)
  80. -- | The number of haddockable and haddocked items in the module, as a
  81. -- tuple. Haddockable items are the exports and the module itself.
  82. , ifaceHaddockCoverage :: (Int,Int)
  83. }
  84. -- | A subset of the fields of 'Interface' that we store in the interface
  85. -- files.
  86. data InstalledInterface = InstalledInterface
  87. {
  88. -- | The module represented by this interface.
  89. instMod :: Module
  90. -- | Textual information about the module.
  91. , instInfo :: HaddockModInfo Name
  92. -- | Documentation of declarations originating from the module (including
  93. -- subordinates).
  94. , instDocMap :: Map Name (DocForDecl Name)
  95. -- | All names exported by this module.
  96. , instExports :: [Name]
  97. -- | All \"visible\" names exported by the module.
  98. -- A visible name is a name that will show up in the documentation of the
  99. -- module.
  100. , instVisibleExports :: [Name]
  101. -- | Haddock options for this module (prune, ignore-exports, etc).
  102. , instOptions :: [DocOption]
  103. , instSubMap :: Map Name [Name]
  104. }
  105. -- | Convert an 'Interface' to an 'InstalledInterface'
  106. toInstalledIface :: Interface -> InstalledInterface
  107. toInstalledIface interface = InstalledInterface
  108. { instMod = ifaceMod interface
  109. , instInfo = ifaceInfo interface
  110. , instDocMap = fmap unrenameDocForDecl $ ifaceRnDocMap interface
  111. , instExports = ifaceExports interface
  112. , instVisibleExports = ifaceVisibleExports interface
  113. , instOptions = ifaceOptions interface
  114. , instSubMap = ifaceSubMap interface
  115. }
  116. -----------------------------------------------------------------------------
  117. -- * Export items & declarations
  118. -----------------------------------------------------------------------------
  119. data ExportItem name
  120. -- | An exported declaration.
  121. = ExportDecl
  122. {
  123. -- | A declaration.
  124. expItemDecl :: LHsDecl name
  125. -- | Maybe a doc comment, and possibly docs for arguments (if this
  126. -- decl is a function or type-synonym).
  127. , expItemMbDoc :: DocForDecl name
  128. -- | Subordinate names, possibly with documentation.
  129. , expItemSubDocs :: [(name, DocForDecl name)]
  130. -- | Instances relevant to this declaration, possibly with
  131. -- documentation.
  132. , expItemInstances :: [DocInstance name]
  133. }
  134. -- | An exported entity for which we have no documentation (perhaps because it
  135. -- resides in another package).
  136. | ExportNoDecl
  137. { expItemName :: name
  138. -- | Subordinate names.
  139. , expItemSubs :: [name]
  140. }
  141. -- | A section heading.
  142. | ExportGroup
  143. {
  144. -- | Section level (1, 2, 3, ...).
  145. expItemSectionLevel :: Int
  146. -- | Section id (for hyperlinks).
  147. , expItemSectionId :: String
  148. -- | Section heading text.
  149. , expItemSectionText :: Doc name
  150. }
  151. -- | Some documentation.
  152. | ExportDoc (Doc name)
  153. -- | A cross-reference to another module.
  154. | ExportModule Module
  155. -- | A declaration that may have documentation, including its subordinates,
  156. -- which may also have documentation.
  157. type DeclInfo = (Decl, DocForDecl Name, [(Name, DocForDecl Name)])
  158. -- | Arguments and result are indexed by Int, zero-based from the left,
  159. -- because that's the easiest to use when recursing over types.
  160. type FnArgsDoc name = Map Int (Doc name)
  161. type DocForDecl name = (Maybe (Doc name), FnArgsDoc name)
  162. noDocForDecl :: DocForDecl name
  163. noDocForDecl = (Nothing, Map.empty)
  164. unrenameDocForDecl :: DocForDecl DocName -> DocForDecl Name
  165. unrenameDocForDecl (mbDoc, fnArgsDoc) =
  166. (fmap unrenameDoc mbDoc, fmap unrenameDoc fnArgsDoc)
  167. -----------------------------------------------------------------------------
  168. -- * Cross-referencing
  169. -----------------------------------------------------------------------------
  170. -- | Type of environment used to cross-reference identifiers in the syntax.
  171. type LinkEnv = Map Name Module
  172. -- | Extends 'Name' with cross-reference information.
  173. data DocName
  174. = Documented Name Module
  175. -- ^ This thing is part of the (existing or resulting)
  176. -- documentation. The 'Module' is the preferred place
  177. -- in the documentation to refer to.
  178. | Undocumented Name
  179. -- ^ This thing is not part of the (existing or resulting)
  180. -- documentation, as far as Haddock knows.
  181. deriving Eq
  182. instance NamedThing DocName where
  183. getName (Documented name _) = name
  184. getName (Undocumented name) = name
  185. -----------------------------------------------------------------------------
  186. -- * Instances
  187. -----------------------------------------------------------------------------
  188. -- | An instance head that may have documentation.
  189. type DocInstance name = (InstHead name, Maybe (Doc name))
  190. -- | The head of an instance. Consists of a context, a class name and a list
  191. -- of instance types.
  192. type InstHead name = ([HsPred name], name, [HsType name])
  193. -----------------------------------------------------------------------------
  194. -- * Documentation comments
  195. -----------------------------------------------------------------------------
  196. type LDoc id = Located (Doc id)
  197. data Doc id
  198. = DocEmpty
  199. | DocAppend (Doc id) (Doc id)
  200. | DocString String
  201. | DocParagraph (Doc id)
  202. | DocIdentifier [id]
  203. | DocModule String
  204. | DocEmphasis (Doc id)
  205. | DocMonospaced (Doc id)
  206. | DocUnorderedList [Doc id]
  207. | DocOrderedList [Doc id]
  208. | DocDefList [(Doc id, Doc id)]
  209. | DocCodeBlock (Doc id)
  210. | DocURL String
  211. | DocPic String
  212. | DocAName String
  213. | DocExamples [Example]
  214. deriving (Eq, Show, Functor)
  215. unrenameDoc :: Doc DocName -> Doc Name
  216. unrenameDoc = fmap getName
  217. data Example = Example
  218. { exampleExpression :: String
  219. , exampleResult :: [String]
  220. } deriving (Eq, Show)
  221. exampleToString :: Example -> String
  222. exampleToString (Example expression result) =
  223. ">>> " ++ expression ++ "\n" ++ unlines result
  224. data DocMarkup id a = Markup
  225. { markupEmpty :: a
  226. , markupString :: String -> a
  227. , markupParagraph :: a -> a
  228. , markupAppend :: a -> a -> a
  229. , markupIdentifier :: [id] -> a
  230. , markupModule :: String -> a
  231. , markupEmphasis :: a -> a
  232. , markupMonospaced :: a -> a
  233. , markupUnorderedList :: [a] -> a
  234. , markupOrderedList :: [a] -> a
  235. , markupDefList :: [(a,a)] -> a
  236. , markupCodeBlock :: a -> a
  237. , markupURL :: String -> a
  238. , markupAName :: String -> a
  239. , markupPic :: String -> a
  240. , markupExample :: [Example] -> a
  241. }
  242. data HaddockModInfo name = HaddockModInfo
  243. { hmi_description :: Maybe (Doc name)
  244. , hmi_portability :: Maybe String
  245. , hmi_stability :: Maybe String
  246. , hmi_maintainer :: Maybe String
  247. }
  248. emptyHaddockModInfo :: HaddockModInfo a
  249. emptyHaddockModInfo = HaddockModInfo
  250. { hmi_description = Nothing
  251. , hmi_portability = Nothing
  252. , hmi_stability = Nothing
  253. , hmi_maintainer = Nothing
  254. }
  255. -----------------------------------------------------------------------------
  256. -- * Options
  257. -----------------------------------------------------------------------------
  258. {-! for DocOption derive: Binary !-}
  259. -- | Source-level options for controlling the documentation.
  260. data DocOption
  261. = OptHide -- ^ This module should not appear in the docs.
  262. | OptPrune
  263. | OptIgnoreExports -- ^ Pretend everything is exported.
  264. | OptNotHome -- ^ Not the best place to get docs for things
  265. -- exported by this module.
  266. deriving (Eq, Show)
  267. -- | Option controlling how to qualify names
  268. data Qualification
  269. = NoQual -- ^ Never qualify any names.
  270. | FullQual -- ^ Qualify all names fully.
  271. | LocalQual (Maybe Module) -- ^ Qualify all imported names fully.
  272. | RelativeQual (Maybe Module) -- ^ Like local, but strip module prefix.
  273. -- from modules in the same hierarchy.
  274. -----------------------------------------------------------------------------
  275. -- * Error handling
  276. -----------------------------------------------------------------------------
  277. -- A monad which collects error messages, locally defined to avoid a dep on mtl
  278. type ErrMsg = String
  279. newtype ErrMsgM a = Writer { runWriter :: (a, [ErrMsg]) }
  280. instance Functor ErrMsgM where
  281. fmap f (Writer (a, msgs)) = Writer (f a, msgs)
  282. instance Monad ErrMsgM where
  283. return a = Writer (a, [])
  284. m >>= k = Writer $ let
  285. (a, w) = runWriter m
  286. (b, w') = runWriter (k a)
  287. in (b, w ++ w')
  288. tell :: [ErrMsg] -> ErrMsgM ()
  289. tell w = Writer ((), w)
  290. -- Exceptions
  291. -- | Haddock's own exception type.
  292. data HaddockException = HaddockException String deriving Typeable
  293. instance Show HaddockException where
  294. show (HaddockException str) = str
  295. throwE :: String -> a
  296. instance Exception HaddockException
  297. throwE str = throw (HaddockException str)
  298. -- In "Haddock.Interface.Create", we need to gather
  299. -- @Haddock.Types.ErrMsg@s a lot, like @ErrMsgM@ does,
  300. -- but we can't just use @GhcT ErrMsgM@ because GhcT requires the
  301. -- transformed monad to be MonadIO.
  302. newtype ErrMsgGhc a = WriterGhc { runWriterGhc :: (Ghc (a, [ErrMsg])) }
  303. --instance MonadIO ErrMsgGhc where
  304. -- liftIO = WriterGhc . fmap (\a->(a,[])) liftIO
  305. --er, implementing GhcMonad involves annoying ExceptionMonad and
  306. --WarnLogMonad classes, so don't bother.
  307. liftGhcToErrMsgGhc :: Ghc a -> ErrMsgGhc a
  308. liftGhcToErrMsgGhc = WriterGhc . fmap (\a->(a,[]))
  309. liftErrMsg :: ErrMsgM a -> ErrMsgGhc a
  310. liftErrMsg = WriterGhc . return . runWriter
  311. -- for now, use (liftErrMsg . tell) for this
  312. --tell :: [ErrMsg] -> ErrMsgGhc ()
  313. --tell msgs = WriterGhc $ return ( (), msgs )
  314. instance Functor ErrMsgGhc where
  315. fmap f (WriterGhc x) = WriterGhc (fmap (first f) x)
  316. instance Monad ErrMsgGhc where
  317. return a = WriterGhc (return (a, []))
  318. m >>= k = WriterGhc $ runWriterGhc m >>= \ (a, msgs1) ->
  319. fmap (second (msgs1 ++)) (runWriterGhc (k a))