1d5b008548e0eec7d5651e344527c1a27385ec92
[ghc-hetmet.git] / ghc / compiler / reader / PrefixToHs.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[PrefixToHS]{Support routines for converting ``prefix form'' to Haskell abstract syntax}
5
6 Support routines for reading prefix-form from the Lex/Yacc parser.
7
8 \begin{code}
9 module PrefixToHs (
10         cvValSig,
11         cvClassOpSig,
12         cvInstDeclSig,
13
14         cvBinds,
15         cvMonoBindsAndSigs,
16         cvMatches,
17         cvOtherDecls,
18         cvForeignDecls -- HACK
19
20     ) where
21
22 #include "HsVersions.h"
23
24 import PrefixSyn        -- and various syntaxen.
25 import HsSyn
26 import RdrHsSyn
27 import HsPragmas        ( noGenPragmas, noClassOpPragmas )
28
29 import BasicTypes       ( RecFlag(..) )
30 import SrcLoc           ( mkSrcLoc )
31 import Util             ( mapAndUnzip, panic, assertPanic )
32 \end{code}
33
34 %************************************************************************
35 %*                                                                      *
36 \subsection[cvDecls]{Convert various top-level declarations}
37 %*                                                                      *
38 %************************************************************************
39
40 We make a point not to throw any user-pragma ``sigs'' at
41 these conversion functions:
42
43 \begin{code}
44 cvValSig, cvClassOpSig, cvInstDeclSig :: SigConverter
45
46 cvValSig      sig = sig
47
48 cvInstDeclSig sig = sig
49
50 cvClassOpSig (Sig var poly_ty src_loc) = ClassOpSig var Nothing poly_ty src_loc
51 cvClassOpSig sig                       = sig
52 \end{code}
53
54
55 %************************************************************************
56 %*                                                                      *
57 \subsection[cvBinds-etc]{Converting to @HsBinds@, @MonoBinds@, etc.}
58 %*                                                                      *
59 %************************************************************************
60
61 Function definitions are restructured here. Each is assumed to be recursive
62 initially, and non recursive definitions are discovered by the dependency
63 analyser.
64
65 \begin{code}
66 cvBinds :: SrcFile -> SigConverter -> RdrBinding -> RdrNameHsBinds
67 cvBinds sf sig_cvtr binding
68   = case (cvMonoBindsAndSigs sf sig_cvtr binding) of { (mbs, sigs) ->
69     MonoBind mbs sigs Recursive
70     }
71 \end{code}
72
73 \begin{code}
74 cvMonoBindsAndSigs :: SrcFile
75                    -> SigConverter
76                    -> RdrBinding
77                    -> (RdrNameMonoBinds, [RdrNameSig])
78
79 cvMonoBindsAndSigs sf sig_cvtr fb
80   = mangle_bind (EmptyMonoBinds, []) fb
81   where
82     -- If the function being bound has at least one argument, then the
83     -- guarded right hand sides of each pattern binding are knitted
84     -- into a series of patterns, each matched with its corresponding
85     -- guarded right hand side (which may contain several
86     -- alternatives). This series is then paired with the name of the
87     -- function. Otherwise there is only one pattern, which is paired
88     -- with a guarded right hand side.
89
90     mangle_bind acc (RdrAndBindings fb1 fb2)
91       = mangle_bind (mangle_bind acc fb1) fb2
92
93     mangle_bind (b_acc, s_acc) (RdrSig sig)
94       = (b_acc, sig_cvtr sig : s_acc)
95
96     mangle_bind (b_acc, s_acc)
97                 (RdrPatternBinding lousy_srcline [patbinding])
98       -- WDP: the parser has trouble getting a good line-number on RdrPatternBindings.
99       = case (cvPatMonoBind sf patbinding) of { (pat, grhss, binds) ->
100         let
101             src_loc = mkSrcLoc sf good_srcline
102         in
103         (b_acc `AndMonoBinds`
104          PatMonoBind pat (GRHSsAndBindsIn grhss binds) src_loc, s_acc)
105         }
106       where
107         good_srcline = case patbinding of
108                          RdrMatch_NoGuard ln _ _ _ _ -> ln
109                          RdrMatch_Guards  ln _ _ _ _ -> ln
110
111
112     mangle_bind _ (RdrPatternBinding _ _)
113       = panic "mangleBinding: more than one pattern on a RdrPatternBinding"
114
115     mangle_bind (b_acc, s_acc) (RdrFunctionBinding srcline patbindings)
116             -- must be a function binding...
117       = case (cvFunMonoBind sf patbindings) of { (var, inf, matches) ->
118         (b_acc `AndMonoBinds`
119          FunMonoBind var inf matches (mkSrcLoc sf srcline), s_acc)
120         }
121
122     mangle_bind (b_acc, s_acc) other = (b_acc, s_acc)
123         -- Ignore class decls, instance decls etc
124 \end{code}
125
126 \begin{code}
127 cvPatMonoBind :: SrcFile -> RdrMatch -> (RdrNamePat, [RdrNameGRHS], RdrNameHsBinds)
128
129 cvPatMonoBind sf (RdrMatch_NoGuard srcline srcfun pat expr binding)
130   = (pat, unguardedRHS expr (mkSrcLoc sf srcline), cvBinds sf cvValSig binding)
131
132 cvPatMonoBind sf (RdrMatch_Guards srcline srcfun pat guardedexprs binding)
133   = (pat, map (cvGRHS sf srcline) guardedexprs, cvBinds sf cvValSig binding)
134
135 cvFunMonoBind :: SrcFile -> [RdrMatch] -> (RdrName {-VarName-}, Bool {-InfixDefn-}, [RdrNameMatch])
136
137 cvFunMonoBind sf matches
138   = (head srcfuns, head infixdefs, cvMatches sf False matches)
139   where
140     (srcfuns, infixdefs) = mapAndUnzip get_mdef matches
141     -- ToDo: Check for consistent srcfun and infixdef
142
143     get_mdef (RdrMatch_NoGuard _ sfun pat _ _) = get_pdef pat
144     get_mdef (RdrMatch_Guards  _ sfun pat _ _) = get_pdef pat
145
146     get_pdef (ConPatIn fn _)       = (fn, False)
147     get_pdef (ConOpPatIn _ op _ _) = (op, True)
148     get_pdef (ParPatIn pat)        = get_pdef pat
149
150
151 cvMatches :: SrcFile -> Bool -> [RdrMatch] -> [RdrNameMatch]
152 cvMatch   :: SrcFile -> Bool -> RdrMatch   -> RdrNameMatch
153
154 cvMatches sf is_case matches = map (cvMatch sf is_case) matches
155
156 cvMatch sf is_case rdr_match
157   = foldr PatMatch
158           (GRHSMatch (GRHSsAndBindsIn guarded_exprs (cvBinds sf cvValSig binding)))
159
160           -- For a FunMonoBinds, the first flattened "pattern" is
161           -- just the function name, and we don't want to keep it.
162           -- For a case expr, it's (presumably) a constructor name -- and
163           -- we most certainly want to keep it!  Hence the monkey busines...
164
165           (if is_case then -- just one pattern: leave it untouched...
166               [pat]
167            else            -- function pattern; extract arg patterns...
168               case pat of ConPatIn fn pats      -> pats
169                           ConOpPatIn p1 op _ p2 -> [p1,p2]
170                           ParPatIn pat          -> panic "PrefixToHs.cvMatch:ParPatIn"
171           )
172   where
173     (pat, binding, guarded_exprs)
174       = case rdr_match of
175           RdrMatch_NoGuard ln b c expr    d -> (c,d, unguardedRHS expr (mkSrcLoc sf ln))
176           RdrMatch_Guards  ln b c gd_exps d -> (c,d, map (cvGRHS sf ln) gd_exps)
177
178 cvGRHS :: SrcFile -> SrcLine -> ([RdrNameStmt], RdrNameHsExpr) -> RdrNameGRHS
179 cvGRHS sf sl (g, e) = GRHS g e (mkSrcLoc sf sl)
180 \end{code}
181
182 %************************************************************************
183 %*                                                                      *
184 \subsection[PrefixToHS-utils]{Utilities for conversion}
185 %*                                                                      *
186 %************************************************************************
187
188 Separate declarations into all the various kinds:
189
190 \begin{code}
191 cvOtherDecls :: RdrBinding -> [RdrNameHsDecl]
192 cvOtherDecls b 
193   = go [] b
194   where
195     go acc (RdrAndBindings b1 b2) = go (go acc b1) b2
196     go acc (RdrTyDecl d)          = TyD d   : acc
197     go acc (RdrClassDecl d)       = ClD d   : acc
198     go acc (RdrInstDecl d)        = InstD d : acc 
199     go acc (RdrDefaultDecl d)     = DefD d  : acc
200     go acc other                  = acc
201         -- Ignore value bindings
202
203 cvForeignDecls :: RdrBinding -> [RdrNameHsDecl]
204 cvForeignDecls b = go [] b
205  where
206     go acc (RdrAndBindings b1 b2) = go (go acc b1) b2
207     go acc (RdrForeignDecl d)     = ForD d  : acc
208     go acc other                  = acc
209  
210 \end{code}