aboutsummaryrefslogtreecommitdiff
path: root/src/Haddock/Types.hs
blob: 4c4587ac1c3cf4456bbc2fc77e74b43fadab91d8 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
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
}