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