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