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