45d1ec05a24233e303ad28b5c0e20ed54e42ac76
[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
26         HaddockModInfo(..),
27         emptyHaddockModInfo,
28 ) where
29
30 -- friends:
31 import HsDecls          
32 import HsBinds
33 import HsExpr
34 import HsImpExp
35 import HsLit
36 import HsPat
37 import HsTypes
38 import BasicTypes       ( Fixity, WarningTxt )
39 import HsUtils
40 import HsDoc
41
42 -- others:
43 import IfaceSyn         ( IfaceBinding )
44 import Outputable
45 import SrcLoc           ( Located(..) )
46 import Module           ( Module, ModuleName )
47 import FastString
48 \end{code}
49
50 \begin{code}
51 -- | All we actually declare here is the top-level structure for a module.
52 data HsModule name
53   = HsModule {
54       hsmodName :: Maybe (Located ModuleName),
55         -- ^ @Nothing@: \"module X where\" is omitted (in which case the next
56         --     field is Nothing too)
57       hsmodExports :: Maybe [LIE name],
58         -- ^ Export list
59         --
60         --  - @Nothing@: export list omitted, so export everything
61         --
62         --  - @Just []@: export /nothing/
63         --
64         --  - @Just [...]@: as you would expect...
65         --
66       hsmodImports :: [LImportDecl name],
67         -- ^ We snaffle interesting stuff out of the imported interfaces early
68         -- on, adding that info to TyDecls/etc; so this list is often empty,
69         -- downstream.
70       hsmodDecls :: [LHsDecl name],
71         -- ^ Type, class, value, and interface signature decls
72       hsmodDeprecMessage :: Maybe WarningTxt,
73         -- ^ reason\/explanation for warning/deprecation of this module
74       hsmodHaddockModInfo :: HaddockModInfo name,
75         -- ^ Haddock module info
76       hsmodHaddockModDescr :: Maybe (HsDoc name)
77         -- ^ Haddock module description
78    }
79
80 data HaddockModInfo name = HaddockModInfo { 
81         hmi_description :: Maybe (HsDoc name),
82         hmi_portability :: Maybe String,
83         hmi_stability   :: Maybe String,
84         hmi_maintainer  :: Maybe String
85 }
86
87 emptyHaddockModInfo :: HaddockModInfo a                                                  
88 emptyHaddockModInfo = HaddockModInfo {                                                  
89         hmi_description = Nothing,
90         hmi_portability = Nothing,
91         hmi_stability   = Nothing,
92         hmi_maintainer  = Nothing
93 }       
94
95 data HsExtCore name     -- Read from Foo.hcr
96   = HsExtCore
97         Module
98         [TyClDecl name] -- Type declarations only; just as in Haskell source,
99                         -- so that we can infer kinds etc
100         [IfaceBinding]  -- And the bindings
101 \end{code}
102
103
104 \begin{code}
105 instance Outputable Char where
106   ppr c = text [c]
107
108 instance (OutputableBndr name)
109         => Outputable (HsModule name) where
110
111     ppr (HsModule Nothing _ imports decls _ _ mbDoc)
112       = pp_mb mbDoc $$ pp_nonnull imports $$ pp_nonnull decls
113
114     ppr (HsModule (Just name) exports imports decls deprec _ mbDoc)
115       = vcat [
116             pp_mb mbDoc,
117             case exports of
118               Nothing -> pp_header (ptext (sLit "where"))
119               Just es -> vcat [
120                            pp_header lparen,
121                            nest 8 (fsep (punctuate comma (map ppr es))),
122                            nest 4 (ptext (sLit ") where"))
123                           ],
124             pp_nonnull imports,
125             pp_nonnull decls
126           ]
127       where
128         pp_header rest = case deprec of
129            Nothing -> pp_modname <+> rest
130            Just d -> vcat [ pp_modname, ppr d, rest ]
131
132         pp_modname = ptext (sLit "module") <+> ppr name
133
134 pp_mb :: Outputable t => Maybe t -> SDoc
135 pp_mb (Just x) = ppr x 
136 pp_mb Nothing  = empty
137
138 pp_nonnull :: Outputable t => [t] -> SDoc
139 pp_nonnull [] = empty
140 pp_nonnull xs = vcat (map ppr xs)
141 \end{code}