[project @ 1996-06-26 10:26:00 by partain]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsSyn.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
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 #include "HsVersions.h"
12
13 module HsSyn (
14
15         -- NB: don't reexport HsCore or HsPragmas;
16         -- this module tells about "real Haskell"
17
18         EXP_MODULE(HsSyn) ,
19 #if (! defined(REALLY_HASKELL_1_3)) || PATRICK_FIXES_MODULE_DOTDOT_THING
20         EXP_MODULE(HsBinds) ,
21         EXP_MODULE(HsDecls) ,
22         EXP_MODULE(HsExpr) ,
23         EXP_MODULE(HsImpExp) ,
24         EXP_MODULE(HsLit) ,
25         EXP_MODULE(HsMatches) ,
26         EXP_MODULE(HsPat) ,
27         EXP_MODULE(HsTypes)
28 #else
29         ArithSeqInfo(..),
30         BangType(..),
31         Bind(..),
32         ClassDecl(..),
33         ConDecl(..),
34         DefaultDecl(..),
35         FixityDecl(..),
36         GRHS(..),
37         GRHSsAndBinds(..),
38         HsBinds(..),
39         HsExpr(..),
40         HsLit(..),
41         IE(..),
42         ImportDecl(..),
43         InPat(..),
44         InstDecl(..),
45         Match(..),
46         MonoBinds(..),
47         MonoType(..),
48         OutPat(..),
49         PolyType(..),
50         Qualifier(..),
51         Sig(..),
52         SpecDataSig(..),
53         SpecInstSig(..),
54         Stmt(..),
55         TyDecl(..),
56         bindIsRecursive,
57         cmpContext,
58         cmpMonoType,
59         cmpPolyType,
60         collectBinders,
61         collectMonoBinders,
62         collectMonoBindersAndLocs,
63         collectPatBinders,
64         collectTopLevelBinders,
65         extractCtxtTyNames,
66         extractMonoTyNames,
67         failureFreePat,
68         irrefutablePat,
69         irrefutablePats,
70         isConPat,
71         isLitPat,
72         negLiteral,
73         nullBind,
74         nullBinds,
75         nullMonoBinds,
76         patsAreAllCons,
77         patsAreAllLits,
78         pp_condecls,
79         pp_decl_head,
80         pp_dotdot,
81         pp_rbinds,
82         pp_tydecl,
83         pprContext,
84         pprExpr,
85         pprGRHS,
86         pprGRHSsAndBinds,
87         pprMatch,
88         pprMatches,
89         pprParendExpr,
90         pprParendMonoType,
91         pprParendPolyType,
92         ppr_bang,
93         print_it,
94         SYN_IE(ClassAssertion),
95         SYN_IE(Context),
96         SYN_IE(HsRecordBinds)
97 #endif
98      ) where
99
100 IMP_Ubiq()
101
102 -- friends:
103 import HsBinds
104 import HsDecls
105 import HsExpr
106 import HsImpExp
107 import HsLit
108 import HsMatches
109 import HsPat
110 import HsTypes
111 import HsPragmas        ( ClassPragmas, ClassOpPragmas,
112                           DataPragmas, GenPragmas, InstancePragmas )
113 -- others:
114 import FiniteMap        ( FiniteMap )
115 import Outputable       ( ifPprShowAll, ifnotPprForUser, interpp'SP, Outputable(..) )
116 import Pretty
117 import SrcLoc           ( SrcLoc )
118 \end{code}
119
120 @Fake@ is a placeholder type; for when tyvars and uvars aren't used.
121 \begin{code}
122 data Fake = Fake
123 instance Eq Fake
124 instance Outputable Fake
125 \end{code}
126
127 All we actually declare here is the top-level structure for a module.
128 \begin{code}
129 type Version = Int
130
131 data HsModule tyvar uvar name pat
132   = HsModule
133         Module                  -- module name
134         (Maybe Version)         -- source interface version number
135         (Maybe [IE name])       -- export list; Nothing => export everything
136                                 -- Just [] => export *nothing* (???)
137                                 -- Just [...] => as you would expect...
138         [ImportDecl name]       -- We snaffle interesting stuff out of the
139                                 -- imported interfaces early on, adding that
140                                 -- info to TyDecls/etc; so this list is
141                                 -- often empty, downstream.
142         [FixityDecl name]
143         [TyDecl name]
144         [SpecDataSig name]              -- user pragmas that modify TyDecls
145         [ClassDecl tyvar uvar name pat]
146         [InstDecl  tyvar uvar name pat]
147         [SpecInstSig name]              -- user pragmas that modify InstDecls
148         [DefaultDecl name]
149         (HsBinds tyvar uvar name pat)   -- the main stuff, includes source sigs
150         [Sig name]                      -- interface sigs
151         SrcLoc
152 \end{code}
153
154 \begin{code}
155 instance (NamedThing name, Outputable name, Outputable pat,
156           Eq tyvar, Outputable tyvar, Eq uvar, Outputable uvar)
157         => Outputable (HsModule tyvar uvar name pat) where
158
159     ppr sty (HsModule name iface_version exports imports fixities
160                       typedecls typesigs classdecls instdecls instsigs
161                       defdecls binds sigs src_loc)
162       = ppAboves [
163             ifPprShowAll sty (ppr sty src_loc),
164             ifnotPprForUser sty (pp_iface_version iface_version),
165             case exports of
166               Nothing -> ppCat [ppPStr SLIT("module"), ppPStr name, ppPStr SLIT("where")]
167               Just es -> ppAboves [
168                             ppCat [ppPStr SLIT("module"), ppPStr name, ppLparen],
169                             ppNest 8 (interpp'SP sty es),
170                             ppNest 4 (ppPStr SLIT(") where"))
171                           ],
172             pp_nonnull imports,
173             pp_nonnull fixities,
174             pp_nonnull typedecls,
175             pp_nonnull typesigs,
176             pp_nonnull classdecls,
177             pp_nonnull instdecls,
178             pp_nonnull instsigs,
179             pp_nonnull defdecls,
180             ppr sty binds,
181             pp_nonnull sigs
182         ]
183       where
184         pp_nonnull [] = ppNil
185         pp_nonnull xs = ppAboves (map (ppr sty) xs)
186
187         pp_iface_version Nothing  = ppNil
188         pp_iface_version (Just n) = ppCat [ppStr "{-# INTERFACE", ppInt n, ppStr "#-}"]
189 \end{code}