aboutsummaryrefslogtreecommitdiff
path: root/src/Haddock/Types.hs
diff options
context:
space:
mode:
authordavve@dtek.chalmers.se <David Waern>2007-03-25 01:23:25 +0000
committerdavve@dtek.chalmers.se <David Waern>2007-03-25 01:23:25 +0000
commit11ebf08d5ef30375ba5585b6079f696d49402c3f (patch)
tree0287ff78e5f7f0658010c6c18993415693bd9ab9 /src/Haddock/Types.hs
parentbc59490468c17bfc181ffe51cf428314195ad8a0 (diff)
De-flatten the namespace
Diffstat (limited to 'src/Haddock/Types.hs')
-rw-r--r--src/Haddock/Types.hs123
1 files changed, 123 insertions, 0 deletions
diff --git a/src/Haddock/Types.hs b/src/Haddock/Types.hs
new file mode 100644
index 00000000..4c4587ac
--- /dev/null
+++ b/src/Haddock/Types.hs
@@ -0,0 +1,123 @@
+--
+-- Haddock - A Haskell Documentation Tool
+--
+-- (c) Simon Marlow 2003
+--
+-- Ported to use the GHC API by David Waern 2006
+--
+
+module Haddock.Types where
+
+import GHC
+import Outputable
+
+import Data.Map
+
+data DocOption
+ = 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.
+ deriving (Eq, Show)
+
+data ExportItem name
+ = ExportDecl
+ Name -- ^ The original name
+ (LHsDecl name) -- ^ A declaration
+ (Maybe (HsDoc name)) -- ^ Maybe a doc comment
+ [InstHead name] -- ^ Instances relevant to this declaration
+
+ | ExportNoDecl -- ^ An exported entity for which we have no
+ -- documentation (perhaps because it resides in
+ -- another package)
+ Name -- ^ The original name
+ name -- ^ Where to link to
+ [name] -- ^ Subordinate names
+
+ | ExportGroup -- ^ A section heading
+ Int -- ^ section level (1, 2, 3, ... )
+ String -- ^ Section "id" (for hyperlinks)
+ (HsDoc name) -- ^ Section heading text
+
+ | ExportDoc -- ^ Some documentation
+ (HsDoc name)
+
+ | ExportModule -- ^ A cross-reference to another module
+ Module
+
+type InstHead name = ([HsPred name], name, [HsType name])
+type ModuleMap = Map Module HaddockModule
+type DocMap = Map Name (HsDoc DocName)
+type DocEnv = Map Name Name
+
+data DocName = Link Name | NoLink Name
+
+instance Outputable DocName where
+ ppr (Link n) = ppr n
+ ppr (NoLink n) = ppr n
+
+data HaddockModule = HM {
+
+ -- | A value to identify the module
+ hmod_mod :: Module,
+
+ -- | The original filename for this module
+ hmod_orig_filename :: FilePath,
+
+ -- | Textual information about the module
+ hmod_info :: HaddockModInfo Name,
+
+ -- | The documentation header for this module
+ hmod_doc :: Maybe (HsDoc Name),
+
+ -- | The renamed documentation header for this module
+ hmod_rn_doc :: Maybe (HsDoc DocName),
+
+ -- | The Haddock options for this module (prune, ignore-exports, etc)
+ hmod_options :: [DocOption],
+
+ hmod_exported_decl_map :: Map Name (LHsDecl Name),
+ hmod_doc_map :: Map Name (HsDoc Name),
+ hmod_rn_doc_map :: Map Name (HsDoc DocName),
+
+ hmod_export_items :: [ExportItem Name],
+ hmod_rn_export_items :: [ExportItem DocName],
+
+ -- | All the names that are defined in this module
+ hmod_locals :: [Name],
+
+ -- | All the names that are exported by this module
+ hmod_exports :: [Name],
+
+ -- | All the visible names exported by this module
+ -- For a name to be visible, it has to:
+ -- - be exported normally, and not via a full module re-exportation.
+ -- - have a declaration in this module or any of it's imports, with the
+ -- exception that it can't be from another package.
+ -- Basically, a visible name is a name that will show up in the documentation
+ -- for this module.
+ hmod_visible_exports :: [Name],
+
+ hmod_sub_map :: Map Name [Name],
+
+ -- | The instances exported by this module
+ hmod_instances :: [Instance]
+}
+
+data DocMarkup id a = Markup {
+ markupEmpty :: a,
+ markupString :: String -> a,
+ markupParagraph :: a -> a,
+ markupAppend :: a -> a -> a,
+ markupIdentifier :: [id] -> a,
+ markupModule :: String -> a,
+ markupEmphasis :: a -> a,
+ markupMonospaced :: a -> a,
+ markupUnorderedList :: [a] -> a,
+ markupOrderedList :: [a] -> a,
+ markupDefList :: [(a,a)] -> a,
+ markupCodeBlock :: a -> a,
+ markupURL :: String -> a,
+ markupAName :: String -> a
+}