[project @ 2002-09-09 12:57:47 by simonpj]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsPat.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[PatSyntax]{Abstract Haskell syntax---patterns}
5
6 \begin{code}
7 module HsPat (
8         InPat(..),
9         OutPat(..),
10
11         irrefutablePat, irrefutablePats,
12         failureFreePat, isWildPat, 
13         patsAreAllCons, isConPat, isSigPat,
14         patsAreAllLits, isLitPat,
15         collectPatBinders, collectOutPatBinders, collectPatsBinders,
16         collectSigTysFromPat, collectSigTysFromPats
17     ) where
18
19 #include "HsVersions.h"
20
21
22 -- friends:
23 import HsLit            ( HsLit, HsOverLit )
24 import HsExpr           ( HsExpr )
25 import HsTypes          ( HsType, SyntaxName )
26 import BasicTypes       ( Fixity, Boxity, tupleParens )
27
28 -- others:
29 import Name             ( Name )
30 import Var              ( Id, TyVar )
31 import DataCon          ( DataCon, dataConTyCon )
32 import Name             ( isDataSymOcc, getOccName, NamedThing )
33 import Maybes           ( maybeToBool )
34 import Outputable       
35 import TyCon            ( maybeTyConSingleCon )
36 import Type             ( Type )
37 \end{code}
38
39 Patterns come in distinct before- and after-typechecking flavo(u)rs.
40 \begin{code}
41 data InPat name
42   = WildPatIn                           -- wild card
43   | VarPatIn        name                -- variable
44   | LitPatIn        HsLit               -- literal
45   | LazyPatIn       (InPat name)        -- lazy pattern
46   | AsPatIn         name                -- as pattern
47                     (InPat name)
48   | SigPatIn        (InPat name)
49                     (HsType name)
50   | ConPatIn        name                -- constructed type
51                     [InPat name]
52   | ConOpPatIn      (InPat name)
53                     name
54                     Fixity              -- c.f. OpApp in HsExpr
55                     (InPat name)
56
57   | NPatIn          HsOverLit           -- Always positive
58                     (Maybe SyntaxName)  -- Just (Name of 'negate') for negative
59                                         -- patterns, Nothing otherwise
60
61   | NPlusKPatIn     name                -- n+k pattern
62                     HsOverLit           -- It'll always be an HsIntegral
63                     SyntaxName          -- Name of '-' (see RnEnv.lookupSyntaxName)
64
65   -- We preserve prefix negation and parenthesis for the precedence parser.
66
67   | ParPatIn        (InPat name)        -- parenthesised pattern
68
69   | ListPatIn       [InPat name]        -- syntactic list
70                                         -- must have >= 1 elements
71   | PArrPatIn       [InPat name]        -- syntactic parallel array
72                                         -- must have >= 1 elements
73   | TuplePatIn      [InPat name] Boxity -- tuple (boxed?)
74
75   | RecPatIn        name                -- record
76                     [(name, InPat name, Bool)]  -- True <=> source used punning
77
78 -- Generics
79   | TypePatIn       (HsType name)       -- Type pattern for generic definitions
80                                         -- e.g  f{| a+b |} = ...
81                                         -- These show up only in class 
82                                         -- declarations,
83                                         -- and should be a top-level pattern
84
85 -- /Generics
86
87 data OutPat id
88   = WildPat         Type        -- wild card
89   | VarPat          id          -- variable (type is in the Id)
90   | LazyPat         (OutPat id) -- lazy pattern
91   | AsPat           id          -- as pattern
92                     (OutPat id)
93
94   | SigPat          (OutPat id) -- Pattern p
95                     Type        -- Type, t, of the whole pattern
96                     (HsExpr id (OutPat id))
97                                 -- Coercion function,
98                                 -- of type t -> typeof(p)
99
100   | ListPat                     -- Syntactic list
101                     Type        -- The type of the elements
102                     [OutPat id]
103   | PArrPat                     -- Syntactic parallel array
104                     Type        -- The type of the elements
105                     [OutPat id]
106
107   | TuplePat        [OutPat id] -- Tuple
108                     Boxity
109                                 -- UnitPat is TuplePat []
110
111   | ConPat          DataCon
112                     Type        -- the type of the pattern
113                     [TyVar]     -- Existentially bound type variables
114                     [id]        -- Ditto dictionaries
115                     [OutPat id]
116
117   -- ConOpPats are only used on the input side
118
119   | RecPat          DataCon             -- Record constructor
120                     Type                -- The type of the pattern
121                     [TyVar]             -- Existentially bound type variables
122                     [id]                -- Ditto dictionaries
123                     [(Id, OutPat id, Bool)]     -- True <=> source used punning
124
125   | LitPat          -- Used for *non-overloaded* literal patterns:
126                     -- Int#, Char#, Int, Char, String, etc.
127                     HsLit
128                     Type                -- Type of pattern
129
130   | NPat            -- Used for literal patterns where there's an equality function to call
131                     HsLit                       -- The literal is retained so that
132                                                 -- the desugarer can readily identify
133                                                 -- equations with identical literal-patterns
134                                                 -- Always HsInteger, HsRat or HsString.
135                                                 -- *Unlike* NPatIn, for negative literals, the
136                                                 --      literal is acutally negative!
137                     Type                        -- Type of pattern, t
138                     (HsExpr id (OutPat id))     -- Of type t -> Bool; detects match
139
140   | NPlusKPat       id
141                     Integer
142                     Type                        -- Type of pattern, t
143                     (HsExpr id (OutPat id))     -- Of type t -> Bool; detects match
144                     (HsExpr id (OutPat id))     -- Of type t -> t; subtracts k
145
146   | DictPat         -- Used when destructing Dictionaries with an explicit case
147                     [id]                        -- superclass dicts
148                     [id]                        -- methods
149 \end{code}
150
151 Now name in Inpat is not need to be in NAmedThing to be Outputable.
152 Needed by ../deSugar/Check.lhs
153
154 JJQC-2-12-97
155
156 \begin{code}
157 instance (Outputable name) => Outputable (InPat name) where
158     ppr = pprInPat
159
160 pprInPat :: (Outputable name) => InPat name -> SDoc
161
162 pprInPat (WildPatIn)          = char '_'
163 pprInPat (VarPatIn var)       = ppr var
164 pprInPat (LitPatIn s)         = ppr s
165 pprInPat (SigPatIn pat ty)    = ppr pat <+> dcolon <+> ppr ty
166 pprInPat (LazyPatIn pat)      = char '~' <> ppr pat
167 pprInPat (AsPatIn name pat)   = parens (hcat [ppr name, char '@', ppr pat])
168 pprInPat (ParPatIn pat)       = parens (pprInPat pat)
169 pprInPat (ListPatIn pats)     = brackets (interpp'SP pats)
170 pprInPat (PArrPatIn pats)     = pabrackets (interpp'SP pats)
171 pprInPat (TuplePatIn pats bx) = tupleParens bx (interpp'SP pats)
172 pprInPat (NPlusKPatIn n k _)  = parens (hcat [ppr n, char '+', ppr k])
173 pprInPat (NPatIn l _)         = ppr l
174
175 pprInPat (ConPatIn c pats)
176   | null pats = ppr c
177   | otherwise = hsep [ppr c, interppSP pats] -- inner ParPats supply the necessary parens.
178
179 pprInPat (ConOpPatIn pat1 op fixity pat2)
180  = hsep [ppr pat1, ppr op, ppr pat2] -- ParPats put in parens
181
182         -- ToDo: use pprSym to print op (but this involves fiddling various
183         -- contexts & I'm lazy...); *PatIns are *rarely* printed anyway... (WDP)
184
185 pprInPat (RecPatIn con rpats)
186   = hsep [ppr con, braces (hsep (punctuate comma (map (pp_rpat) rpats)))]
187   where
188     pp_rpat (v, _, True) = ppr v
189     pp_rpat (v, p, _)    = hsep [ppr v, char '=', ppr p]
190
191 pprInPat (TypePatIn ty) = ptext SLIT("{|") <> ppr ty <> ptext SLIT("|}")
192
193 -- add parallel array brackets around a document
194 --
195 pabrackets   :: SDoc -> SDoc
196 pabrackets p  = ptext SLIT("[:") <> p <> ptext SLIT(":]")
197 \end{code}
198
199 \begin{code}
200 instance (NamedThing id, Outputable id) => Outputable (OutPat id) where
201     ppr = pprOutPat
202 \end{code}
203
204 \begin{code}
205 pprOutPat (WildPat ty)  = char '_'
206 pprOutPat (VarPat var)  = ppr var
207 pprOutPat (LazyPat pat) = hcat [char '~', ppr pat]
208 pprOutPat (AsPat name pat)
209   = parens (hcat [ppr name, char '@', ppr pat])
210
211 pprOutPat (SigPat pat ty _)   = ppr pat <+> dcolon <+> ppr ty
212
213 pprOutPat (ConPat name ty [] [] [])
214   = ppr name
215
216 -- Kludge to get infix constructors to come out right
217 -- when ppr'ing desugar warnings.
218 pprOutPat (ConPat name ty tyvars dicts pats)
219   = getPprStyle $ \ sty ->
220     parens      $
221     case pats of
222       [p1,p2] 
223         | userStyle sty && isDataSymOcc (getOccName name) ->
224             hsep [ppr p1, ppr name, ppr p2]
225       _ -> hsep [ppr name, interppSP tyvars, interppSP dicts, interppSP pats]
226
227 pprOutPat (ListPat ty pats)      = brackets (interpp'SP pats)
228 pprOutPat (PArrPat ty pats)      = pabrackets (interpp'SP pats)
229 pprOutPat (TuplePat pats boxity) = tupleParens boxity (interpp'SP pats)
230
231 pprOutPat (RecPat con ty tvs dicts rpats)
232   = hsep [ppr con, interppSP tvs, interppSP dicts, braces (hsep (punctuate comma (map (pp_rpat) rpats)))]
233   where
234     pp_rpat (v, _, True) = ppr v
235     pp_rpat (v, p, _)    = hsep [ppr v, char '=', ppr p]
236
237 pprOutPat (LitPat l ty)         = ppr l -- ToDo: print more
238 pprOutPat (NPat   l ty e)       = ppr l -- ToDo: print more
239 pprOutPat (NPlusKPat n k ty e1 e2)              -- ToDo: print more
240   = parens (hcat [ppr n, char '+', integer k])
241
242 pprOutPat (DictPat dicts methods)
243  = parens (sep [ptext SLIT("{-dict-}"),
244                   brackets (interpp'SP dicts),
245                   brackets (interpp'SP methods)])
246
247 \end{code}
248
249 %************************************************************************
250 %*                                                                      *
251 %* predicates for checking things about pattern-lists in EquationInfo   *
252 %*                                                                      *
253 %************************************************************************
254 \subsection[Pat-list-predicates]{Look for interesting things in patterns}
255
256 Unlike in the Wadler chapter, where patterns are either ``variables''
257 or ``constructors,'' here we distinguish between:
258 \begin{description}
259 \item[unfailable:]
260 Patterns that cannot fail to match: variables, wildcards, and lazy
261 patterns.
262
263 These are the irrefutable patterns; the two other categories
264 are refutable patterns.
265
266 \item[constructor:]
267 A non-literal constructor pattern (see next category).
268
269 \item[literal patterns:]
270 At least the numeric ones may be overloaded.
271 \end{description}
272
273 A pattern is in {\em exactly one} of the above three categories; `as'
274 patterns are treated specially, of course.
275
276 The 1.3 report defines what ``irrefutable'' and ``failure-free'' patterns are.
277 \begin{code}
278 irrefutablePats :: [OutPat id] -> Bool
279 irrefutablePats pat_list = all irrefutablePat pat_list
280
281 irrefutablePat (AsPat   _ pat)  = irrefutablePat pat
282 irrefutablePat (WildPat _)      = True
283 irrefutablePat (VarPat  _)      = True
284 irrefutablePat (LazyPat _)      = True
285 irrefutablePat (DictPat ds ms)  = (length ds + length ms) <= 1
286 irrefutablePat other            = False
287
288 failureFreePat :: OutPat id -> Bool
289
290 failureFreePat (WildPat _)                = True
291 failureFreePat (VarPat _)                 = True
292 failureFreePat (LazyPat _)                = True
293 failureFreePat (AsPat _ pat)              = failureFreePat pat
294 failureFreePat (ConPat con tys _ _ pats)  = only_con con && all failureFreePat pats
295 failureFreePat (RecPat con _ _ _ fields)  = only_con con && and [ failureFreePat pat | (_,pat,_) <- fields ]
296 failureFreePat (ListPat _ _)              = False
297 failureFreePat (PArrPat _ _)              = False
298 failureFreePat (TuplePat pats _)          = all failureFreePat pats
299 failureFreePat (DictPat _ _)              = True
300 failureFreePat other_pat                  = False   -- Literals, NPat
301
302 only_con con = maybeToBool (maybeTyConSingleCon (dataConTyCon con))
303 \end{code}
304
305 \begin{code}
306 isWildPat (WildPat _) = True
307 isWildPat other       = False
308
309 patsAreAllCons :: [OutPat id] -> Bool
310 patsAreAllCons pat_list = all isConPat pat_list
311
312 isConPat (AsPat _ pat)          = isConPat pat
313 isConPat (ConPat _ _ _ _ _)     = True
314 isConPat (ListPat _ _)          = True
315 isConPat (PArrPat _ _)          = True
316 isConPat (TuplePat _ _)         = True
317 isConPat (RecPat _ _ _ _ _)     = True
318 isConPat (DictPat ds ms)        = (length ds + length ms) > 1
319 isConPat other                  = False
320
321 isSigPat (SigPat _ _ _) = True
322 isSigPat other          = False
323
324 patsAreAllLits :: [OutPat id] -> Bool
325 patsAreAllLits pat_list = all isLitPat pat_list
326
327 isLitPat (AsPat _ pat)         = isLitPat pat
328 isLitPat (LitPat _ _)          = True
329 isLitPat (NPat   _ _ _)        = True
330 isLitPat (NPlusKPat _ _ _ _ _) = True
331 isLitPat other                 = False
332 \end{code}
333
334 This function @collectPatBinders@ works with the ``collectBinders''
335 functions for @HsBinds@, etc.  The order in which the binders are
336 collected is important; see @HsBinds.lhs@.
337
338 \begin{code}
339 collectPatBinders :: InPat a -> [a]
340 collectPatBinders pat = collect pat []
341
342 collectOutPatBinders :: OutPat a -> [a]
343 collectOutPatBinders pat = collectOut pat []
344
345 collectPatsBinders :: [InPat a] -> [a]
346 collectPatsBinders pats = foldr collect [] pats
347
348 collect WildPatIn                bndrs = bndrs
349 collect (VarPatIn var)           bndrs = var : bndrs
350 collect (LitPatIn _)             bndrs = bndrs
351 collect (SigPatIn pat _)         bndrs = collect pat bndrs
352 collect (LazyPatIn pat)          bndrs = collect pat bndrs
353 collect (AsPatIn a pat)          bndrs = a : collect pat bndrs
354 collect (NPlusKPatIn n _ _)      bndrs = n : bndrs
355 collect (NPatIn _ _)             bndrs = bndrs
356 collect (ConPatIn c pats)        bndrs = foldr collect bndrs pats
357 collect (ConOpPatIn p1 c f p2)   bndrs = collect p1 (collect p2 bndrs)
358 collect (ParPatIn  pat)          bndrs = collect pat bndrs
359 collect (ListPatIn pats)         bndrs = foldr collect bndrs pats
360 collect (PArrPatIn pats)         bndrs = foldr collect bndrs pats
361 collect (TuplePatIn pats _)      bndrs = foldr collect bndrs pats
362 collect (RecPatIn c fields)      bndrs = foldr (\ (f,pat,_) bndrs -> collect pat bndrs) bndrs fields
363 -- Generics
364 collect (TypePatIn ty)           bndrs = bndrs
365 -- assume the type variables do not need to be bound
366
367 -- collect the bounds *value* variables in renamed patterns; type variables
368 -- are *not* collected
369 --
370 collectOut (WildPat _)              bndrs = bndrs
371 collectOut (VarPat var)             bndrs = var : bndrs
372 collectOut (LazyPat pat)            bndrs = collectOut pat bndrs
373 collectOut (AsPat a pat)            bndrs = a : collectOut pat bndrs
374 collectOut (ListPat _ pats)         bndrs = foldr collectOut bndrs pats
375 collectOut (PArrPat _ pats)         bndrs = foldr collectOut bndrs pats
376 collectOut (TuplePat pats _)        bndrs = foldr collectOut bndrs pats
377 collectOut (ConPat _ _ _ ds pats)   bndrs = ds ++ foldr collectOut bndrs pats
378 collectOut (RecPat _ _ _ ds fields) bndrs = ds ++ foldr comb bndrs fields
379   where
380     comb (_, pat, _) bndrs = collectOut pat bndrs
381 collectOut (LitPat _ _)             bndrs = bndrs
382 collectOut (NPat _ _ _)             bndrs = bndrs
383 collectOut (NPlusKPat n _ _ _ _)    bndrs = n : bndrs
384 collectOut (DictPat ids1 ids2)      bndrs = ids1 ++ ids2 ++ bndrs
385 \end{code}
386
387 \begin{code}
388 collectSigTysFromPats :: [InPat name] -> [HsType name]
389 collectSigTysFromPats pats = foldr collect_pat [] pats
390
391 collectSigTysFromPat :: InPat name -> [HsType name]
392 collectSigTysFromPat pat = collect_pat pat []
393
394 collect_pat (SigPatIn pat ty)      acc = collect_pat pat (ty:acc)
395 collect_pat WildPatIn              acc = acc
396 collect_pat (VarPatIn var)         acc = acc
397 collect_pat (LitPatIn _)           acc = acc
398 collect_pat (LazyPatIn pat)        acc = collect_pat pat acc
399 collect_pat (AsPatIn a pat)        acc = collect_pat pat acc
400 collect_pat (NPatIn _ _)           acc = acc
401 collect_pat (NPlusKPatIn n _ _)    acc = acc
402 collect_pat (ConPatIn c pats)      acc = foldr collect_pat acc pats
403 collect_pat (ConOpPatIn p1 c f p2) acc = collect_pat p1 (collect_pat p2 acc)
404 collect_pat (ParPatIn  pat)        acc = collect_pat pat acc
405 collect_pat (ListPatIn pats)       acc = foldr collect_pat acc pats
406 collect_pat (PArrPatIn pats)       acc = foldr collect_pat acc pats
407 collect_pat (TuplePatIn pats _)    acc = foldr collect_pat acc pats
408 collect_pat (RecPatIn c fields)    acc = foldr (\ (f,pat,_) acc -> collect_pat pat acc) acc fields
409 -- Generics
410 collect_pat (TypePatIn ty)         acc = ty:acc
411 \end{code}
412