[project @ 1999-07-15 14:08:03 by keithw]
[ghc-hetmet.git] / ghc / compiler / parser / RdrHsSyn.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1996-1998
3 %
4 \section[RdrHsSyn]{Specialisations of the @HsSyn@ syntax for the reader}
5
6 (Well, really, for specialisations involving @RdrName@s, even if
7 they are used somewhat later on in the compiler...)
8
9 \begin{code}
10 module RdrHsSyn (
11         RdrNameArithSeqInfo,
12         RdrNameBangType,
13         RdrNameClassOpSig,
14         RdrNameConDecl,
15         RdrNameConDetails,
16         RdrNameContext,
17         RdrNameSpecDataSig,
18         RdrNameDefaultDecl,
19         RdrNameForeignDecl,
20         RdrNameGRHS,
21         RdrNameGRHSs,
22         RdrNameHsBinds,
23         RdrNameHsDecl,
24         RdrNameHsExpr,
25         RdrNameHsModule,
26         RdrNameIE,
27         RdrNameImportDecl,
28         RdrNameInstDecl,
29         RdrNameMatch,
30         RdrNameMonoBinds,
31         RdrNamePat,
32         RdrNameHsType,
33         RdrNameHsTyVar,
34         RdrNameSig,
35         RdrNameStmt,
36         RdrNameTyClDecl,
37         RdrNameRuleDecl,
38         RdrNameRuleBndr,
39         RdrNameHsRecordBinds,
40
41         RdrBinding(..),
42         RdrMatch(..),
43         SigConverter,
44
45         RdrNameClassOpPragmas,
46         RdrNameClassPragmas,
47         RdrNameDataPragmas,
48         RdrNameGenPragmas,
49         RdrNameInstancePragmas,
50         extractHsTyRdrNames, 
51         extractHsTyRdrTyVars,
52         extractPatsTyVars, 
53         extractRuleBndrsTyVars,
54  
55         mkOpApp, mkClassDecl, mkClassOpSig,
56
57         cvBinds,
58         cvMonoBindsAndSigs,
59         cvTopDecls,
60         cvValSig, cvClassOpSig, cvInstDeclSig
61     ) where
62
63 #include "HsVersions.h"
64
65 import HsSyn
66 import Name             ( mkClassTyConOcc, mkClassDataConOcc )
67 import OccName          ( mkClassTyConOcc, mkClassDataConOcc, 
68                           mkSuperDictSelOcc, mkDefaultMethodOcc
69                         )
70 import RdrName          ( RdrName, isRdrTyVar, mkRdrUnqual, rdrNameOcc )
71 import Util             ( thenCmp )
72 import HsPragmas        
73 import List             ( nub )
74 import BasicTypes       ( RecFlag(..) )
75 import Outputable
76 \end{code}
77
78  
79 %************************************************************************
80 %*                                                                      *
81 \subsection{Type synonyms}
82 %*                                                                      *
83 %************************************************************************
84
85 \begin{code}
86 type RdrNameArithSeqInfo        = ArithSeqInfo          RdrName RdrNamePat
87 type RdrNameBangType            = BangType              RdrName
88 type RdrNameClassOpSig          = Sig                   RdrName
89 type RdrNameConDecl             = ConDecl               RdrName
90 type RdrNameConDetails          = ConDetails            RdrName
91 type RdrNameContext             = Context               RdrName
92 type RdrNameHsDecl              = HsDecl                RdrName RdrNamePat
93 type RdrNameSpecDataSig         = SpecDataSig           RdrName
94 type RdrNameDefaultDecl         = DefaultDecl           RdrName
95 type RdrNameForeignDecl         = ForeignDecl           RdrName
96 type RdrNameGRHS                = GRHS                  RdrName RdrNamePat
97 type RdrNameGRHSs               = GRHSs                 RdrName RdrNamePat
98 type RdrNameHsBinds             = HsBinds               RdrName RdrNamePat
99 type RdrNameHsExpr              = HsExpr                RdrName RdrNamePat
100 type RdrNameHsModule            = HsModule              RdrName RdrNamePat
101 type RdrNameIE                  = IE                    RdrName
102 type RdrNameImportDecl          = ImportDecl            RdrName
103 type RdrNameInstDecl            = InstDecl              RdrName RdrNamePat
104 type RdrNameMatch               = Match                 RdrName RdrNamePat
105 type RdrNameMonoBinds           = MonoBinds             RdrName RdrNamePat
106 type RdrNamePat                 = InPat                 RdrName
107 type RdrNameHsType              = HsType                RdrName
108 type RdrNameHsTyVar             = HsTyVar               RdrName
109 type RdrNameSig                 = Sig                   RdrName
110 type RdrNameStmt                = Stmt                  RdrName RdrNamePat
111 type RdrNameTyClDecl            = TyClDecl              RdrName RdrNamePat
112 type RdrNameRuleBndr            = RuleBndr              RdrName
113 type RdrNameRuleDecl            = RuleDecl              RdrName RdrNamePat
114
115 type RdrNameHsRecordBinds       = HsRecordBinds         RdrName RdrNamePat
116
117 type RdrNameClassOpPragmas      = ClassOpPragmas        RdrName
118 type RdrNameClassPragmas        = ClassPragmas          RdrName
119 type RdrNameDataPragmas         = DataPragmas           RdrName
120 type RdrNameGenPragmas          = GenPragmas            RdrName
121 type RdrNameInstancePragmas     = InstancePragmas       RdrName
122 \end{code}
123
124
125 %************************************************************************
126 %*                                                                      *
127 \subsection{A few functions over HsSyn at RdrName}
128 %*                                                                    *
129 %************************************************************************
130
131 @extractHsTyRdrNames@ finds the free variables of a HsType
132 It's used when making the for-alls explicit.
133
134 \begin{code}
135 extractHsTyRdrNames :: HsType RdrName -> [RdrName]
136 extractHsTyRdrNames ty = nub (extract_ty ty [])
137
138 extractHsTyRdrTyVars     :: RdrNameHsType -> [RdrName]
139 extractHsTyRdrTyVars ty =  filter isRdrTyVar (extractHsTyRdrNames ty)
140
141 extractRuleBndrsTyVars :: [RuleBndr RdrName] -> [RdrName]
142 extractRuleBndrsTyVars bndrs = filter isRdrTyVar (nub (foldr go [] bndrs))
143                            where
144                              go (RuleBndr _)       acc = acc
145                              go (RuleBndrSig _ ty) acc = extract_ty ty acc
146
147 extractHsCtxtRdrNames :: Context RdrName -> [RdrName]
148 extractHsCtxtRdrNames ty = nub (extract_ctxt ty [])
149
150 extract_ctxt ctxt acc = foldr extract_ass acc ctxt
151                     where
152                       extract_ass (cls, tys) acc = foldr extract_ty (cls : acc) tys
153
154 extract_ty (MonoTyApp ty1 ty2)          acc = extract_ty ty1 (extract_ty ty2 acc)
155 extract_ty (MonoListTy ty)              acc = extract_ty ty acc
156 extract_ty (MonoTupleTy tys _)          acc = foldr extract_ty acc tys
157 extract_ty (MonoFunTy ty1 ty2)          acc = extract_ty ty1 (extract_ty ty2 acc)
158 extract_ty (MonoDictTy cls tys)         acc = foldr extract_ty (cls : acc) tys
159 extract_ty (MonoUsgTy usg ty)           acc = extract_ty ty acc
160 extract_ty (MonoUsgForAllTy uv ty)      acc = extract_ty ty acc
161 extract_ty (MonoTyVar tv)               acc = tv : acc
162 extract_ty (HsForAllTy Nothing ctxt ty) acc = extract_ctxt ctxt (extract_ty ty acc)
163 extract_ty (HsForAllTy (Just tvs) ctxt ty) 
164                                 acc = acc ++
165                                       (filter (`notElem` locals) $
166                                        extract_ctxt ctxt (extract_ty ty []))
167                                     where
168                                       locals = map getTyVarName tvs
169
170
171 extractPatsTyVars :: [RdrNamePat] -> [RdrName]
172 extractPatsTyVars pats = filter isRdrTyVar (nub (foldr extract_pat [] pats))
173
174 extract_pat (SigPatIn pat ty)      acc = extract_ty ty acc
175 extract_pat WildPatIn              acc = acc
176 extract_pat (VarPatIn var)         acc = acc
177 extract_pat (LitPatIn _)           acc = acc
178 extract_pat (LazyPatIn pat)        acc = extract_pat pat acc
179 extract_pat (AsPatIn a pat)        acc = extract_pat pat acc
180 extract_pat (NPlusKPatIn n _)      acc = acc
181 extract_pat (ConPatIn c pats)      acc = foldr extract_pat acc pats
182 extract_pat (ConOpPatIn p1 c f p2) acc = extract_pat p1 (extract_pat p2 acc)
183 extract_pat (NegPatIn  pat)        acc = extract_pat pat acc
184 extract_pat (ParPatIn  pat)        acc = extract_pat pat acc
185 extract_pat (ListPatIn pats)       acc = foldr extract_pat acc pats
186 extract_pat (TuplePatIn pats _)    acc = foldr extract_pat acc pats
187 extract_pat (RecPatIn c fields)    acc = foldr (\ (f,pat,_) acc -> extract_pat pat acc) acc fields
188 \end{code}
189
190 mkClassDecl builds a RdrClassDecl, filling in the names for tycon and datacon
191 by deriving them from the name of the class.  We fill in the names for the
192 tycon and datacon corresponding to the class, by deriving them from the
193 name of the class itself.  This saves recording the names in the interface
194 file (which would be equally good).
195
196 Similarly for mkClassOpSig and default-method names.
197   
198 \begin{code}
199 mkClassDecl cxt cname tyvars sigs mbinds prags loc
200   = ClassDecl cxt cname tyvars sigs mbinds prags tname dname sc_sel_names loc
201   where
202     cls_occ = rdrNameOcc cname
203     dname   = mkRdrUnqual (mkClassDataConOcc cls_occ)
204     tname   = mkRdrUnqual (mkClassTyConOcc   cls_occ)
205     sc_sel_names = [ mkRdrUnqual (mkSuperDictSelOcc n cls_occ) 
206                    | n <- [1..length cxt]]
207       -- We number off the superclass selectors, 1, 2, 3 etc so that we 
208       -- can construct names for the selectors.  Thus
209       --      class (C a, C b) => D a b where ...
210       -- gives superclass selectors
211       --      D_sc1, D_sc2
212       -- (We used to call them D_C, but now we can have two different
213       --  superclasses both called C!)
214
215 mkClassOpSig has_default_method op ty loc
216   | not has_default_method = ClassOpSig op Nothing    ty loc
217   | otherwise              = ClassOpSig op (Just dm_rn) ty loc
218   where
219     dm_rn = mkRdrUnqual (mkDefaultMethodOcc (rdrNameOcc op))
220 \end{code}
221
222 A useful function for building @OpApps@.  The operator is always a variable,
223 and we don't know the fixity yet.
224
225 \begin{code}
226 mkOpApp e1 op e2 = OpApp e1 (HsVar op) (error "mkOpApp:fixity") e2
227 \end{code}
228
229 %************************************************************************
230 %*                                                                      *
231 \subsection[rdrBinding]{Bindings straight out of the parser}
232 %*                                                                      *
233 %************************************************************************
234
235 \begin{code}
236 data RdrBinding
237   =   -- On input we use the Empty/And form rather than a list
238     RdrNullBind
239   | RdrAndBindings    RdrBinding RdrBinding
240
241       -- Value bindings havn't been united with their
242       -- signatures yet
243   | RdrValBinding     RdrNameMonoBinds
244
245       -- Signatures are mysterious; we can't
246       -- tell if its a Sig or a ClassOpSig,
247       -- so we just save the pieces:
248   | RdrSig            RdrNameSig
249
250       -- The remainder all fit into the main HsDecl form
251   | RdrHsDecl         RdrNameHsDecl
252   
253 type SigConverter = RdrNameSig -> RdrNameSig
254 \end{code}
255
256 \begin{code}
257 data RdrMatch
258   = RdrMatch
259              [RdrNamePat]
260              (Maybe RdrNameHsType)
261              RdrNameGRHSs
262 \end{code}
263
264 %************************************************************************
265 %*                                                                      *
266 \subsection[cvDecls]{Convert various top-level declarations}
267 %*                                                                      *
268 %************************************************************************
269
270 We make a point not to throw any user-pragma ``sigs'' at
271 these conversion functions:
272
273 \begin{code}
274 cvValSig, cvClassOpSig, cvInstDeclSig :: SigConverter
275
276 cvValSig      sig = sig
277
278 cvInstDeclSig sig = sig
279
280 cvClassOpSig (Sig var poly_ty src_loc) = ClassOpSig var Nothing poly_ty src_loc
281 cvClassOpSig sig                       = sig
282 \end{code}
283
284
285 %************************************************************************
286 %*                                                                      *
287 \subsection[cvBinds-etc]{Converting to @HsBinds@, @MonoBinds@, etc.}
288 %*                                                                      *
289 %************************************************************************
290
291 Function definitions are restructured here. Each is assumed to be recursive
292 initially, and non recursive definitions are discovered by the dependency
293 analyser.
294
295 \begin{code}
296 cvBinds :: SigConverter -> RdrBinding -> RdrNameHsBinds
297         -- The mysterious SigConverter converts Sigs to ClassOpSigs
298         -- in class declarations.  Mostly it's just an identity function
299
300 cvBinds sig_cvtr binding
301   = case (cvMonoBindsAndSigs sig_cvtr binding) of { (mbs, sigs) ->
302     MonoBind mbs sigs Recursive
303     }
304 \end{code}
305
306 \begin{code}
307 cvMonoBindsAndSigs :: SigConverter
308                    -> RdrBinding
309                    -> (RdrNameMonoBinds, [RdrNameSig])
310
311 cvMonoBindsAndSigs sig_cvtr fb
312   = mangle_bind (EmptyMonoBinds, []) fb
313   where
314     mangle_bind acc RdrNullBind
315       = acc
316
317     mangle_bind acc (RdrAndBindings fb1 fb2)
318       = mangle_bind (mangle_bind acc fb1) fb2
319
320     mangle_bind (b_acc, s_acc) (RdrSig sig)
321       = (b_acc, sig_cvtr sig : s_acc)
322
323     mangle_bind (b_acc, s_acc) (RdrValBinding binding)
324       = (b_acc `AndMonoBinds` binding, s_acc)
325 \end{code}
326
327
328 %************************************************************************
329 %*                                                                      *
330 \subsection[PrefixToHS-utils]{Utilities for conversion}
331 %*                                                                      *
332 %************************************************************************
333
334 Separate declarations into all the various kinds:
335
336 \begin{code}
337 cvTopDecls :: RdrBinding -> [RdrNameHsDecl]
338 cvTopDecls bind
339   = let
340         (top_decls, mono_binds, sigs) = go ([], EmptyMonoBinds, []) bind 
341     in
342     (ValD (MonoBind mono_binds sigs Recursive) : top_decls)
343   where
344     go acc                RdrNullBind            = acc
345     go acc                (RdrAndBindings b1 b2) = go (go acc b1) b2
346     go (topds, mbs, sigs) (RdrHsDecl d)          = (d : topds, mbs, sigs)
347     go (topds, mbs, sigs) (RdrSig (FixSig d))    = (FixD d  : topds, mbs, sigs)
348     go (topds, mbs, sigs) (RdrSig sig)           = (topds, mbs, sig:sigs)
349     go (topds, mbs, sigs) (RdrValBinding bind)   = (topds, mbs `AndMonoBinds` bind, sigs)
350 \end{code}