Merge Haddock comment support from ghc.haddock -- big patch
[ghc-hetmet.git] / compiler / hsSyn / HsSyn.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section{Haskell abstract syntax definition}
5
6 This module glues together the pieces of the Haskell abstract syntax,
7 which is declared in the various \tr{Hs*} modules.  This module,
8 therefore, is almost nothing but re-exporting.
9
10 \begin{code}
11 module HsSyn (
12         module HsBinds,
13         module HsDecls,
14         module HsExpr,
15         module HsImpExp,
16         module HsLit,
17         module HsPat,
18         module HsTypes,
19         module HsUtils,
20         module HsDoc,
21         Fixity,
22
23         HsModule(..), HsExtCore(..),
24
25         HaddockModInfo(..),
26         emptyHaddockModInfo,
27 ) where
28
29 #include "HsVersions.h"
30
31 -- friends:
32 import HsDecls          
33 import HsBinds
34 import HsExpr
35 import HsImpExp
36 import HsLit
37 import HsPat
38 import HsTypes
39 import BasicTypes       ( Fixity, DeprecTxt )
40 import HsUtils
41 import HsDoc
42
43 -- others:
44 import IfaceSyn         ( IfaceBinding )
45 import Outputable
46 import SrcLoc           ( Located(..) )
47 import Module           ( Module, ModuleName )
48 \end{code}
49
50 All we actually declare here is the top-level structure for a module.
51 \begin{code}
52 data HsModule name
53   = HsModule
54         (Maybe (Located ModuleName))-- Nothing => "module X where" is omitted
55                                 --      (in which case the next field is Nothing too)
56         (Maybe [LIE name])      -- Export list; Nothing => export list omitted, so export everything
57                                 -- Just [] => export *nothing*
58                                 -- Just [...] => as you would expect...
59         [LImportDecl name]      -- We snaffle interesting stuff out of the
60                                 -- imported interfaces early on, adding that
61                                 -- info to TyDecls/etc; so this list is
62                                 -- often empty, downstream.
63         [LHsDecl name]          -- Type, class, value, and interface signature decls
64         (Maybe DeprecTxt)       -- reason/explanation for deprecation of this module
65         (Maybe String)          -- Haddock options, declared with the {-# DOCOPTIONS ... #-} pragma
66         (HaddockModInfo name)   -- Haddock module info
67         (Maybe (HsDoc name))    -- Haddock module description
68
69 data HaddockModInfo name = HaddockModInfo { 
70         hmi_description :: Maybe (HsDoc name),
71         hmi_portability :: Maybe String,
72         hmi_stability   :: Maybe String,
73         hmi_maintainer  :: Maybe String
74 }
75
76 emptyHaddockModInfo :: HaddockModInfo a                                                  
77 emptyHaddockModInfo = HaddockModInfo {                                                  
78         hmi_description = Nothing,
79         hmi_portability = Nothing,
80         hmi_stability   = Nothing,
81         hmi_maintainer  = Nothing
82 }       
83
84 data HsExtCore name     -- Read from Foo.hcr
85   = HsExtCore
86         Module
87         [TyClDecl name] -- Type declarations only; just as in Haskell source,
88                         -- so that we can infer kinds etc
89         [IfaceBinding]  -- And the bindings
90 \end{code}
91
92
93 \begin{code}
94 instance Outputable Char where
95   ppr c = text [c]
96
97 instance (OutputableBndr name)
98         => Outputable (HsModule name) where
99
100     ppr (HsModule Nothing _ imports decls _ _ _ mbDoc)
101       = pp_mb mbDoc $$ pp_nonnull imports $$ pp_nonnull decls
102
103     ppr (HsModule (Just name) exports imports decls deprec opts _ mbDoc)
104       = vcat [
105             pp_mb mbDoc,
106             case exports of
107               Nothing -> pp_header (ptext SLIT("where"))
108               Just es -> vcat [
109                            pp_header lparen,
110                            nest 8 (fsep (punctuate comma (map ppr es))),
111                            nest 4 (ptext SLIT(") where"))
112                           ],
113             pp_nonnull imports,
114             pp_nonnull decls
115           ]
116       where
117         pp_header rest = case deprec of
118            Nothing -> pp_modname <+> rest
119            Just d -> vcat [ pp_modname, ppr d, rest ]
120
121         pp_modname = ptext SLIT("module") <+> ppr name
122
123 pp_mb (Just x) = ppr x 
124 pp_mb Nothing  = empty
125
126 pp_nonnull [] = empty
127 pp_nonnull xs = vcat (map ppr xs)
128 \end{code}