2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 \section[PatSyntax]{Abstract Haskell syntax---patterns}
11 irrefutablePat, irrefutablePats,
12 failureFreePat, isWildPat,
13 patsAreAllCons, isConPat,
14 patsAreAllLits, isLitPat,
15 collectPatBinders, collectPatsBinders
18 #include "HsVersions.h"
21 import HsBasic ( HsLit )
22 import HsExpr ( HsExpr )
23 import HsTypes ( HsType )
24 import BasicTypes ( Fixity )
27 import Var ( Id, TyVar )
28 import DataCon ( DataCon, dataConTyCon )
29 import Maybes ( maybeToBool )
31 import TyCon ( maybeTyConSingleCon )
35 Patterns come in distinct before- and after-typechecking flavo(u)rs.
38 = WildPatIn -- wild card
39 | VarPatIn name -- variable
40 | LitPatIn HsLit -- literal
41 | LazyPatIn (InPat name) -- lazy pattern
42 | AsPatIn name -- as pattern
44 | SigPatIn (InPat name)
46 | ConPatIn name -- constructed type
48 | ConOpPatIn (InPat name)
50 Fixity -- c.f. OpApp in HsExpr
53 | NPlusKPatIn name -- n+k pattern
56 -- We preserve prefix negation and parenthesis for the precedence parser.
58 | NegPatIn (InPat name) -- negated pattern
59 | ParPatIn (InPat name) -- parenthesised pattern
61 | ListPatIn [InPat name] -- syntactic list
62 -- must have >= 1 elements
63 | TuplePatIn [InPat name] Bool -- tuple (boxed?)
65 | RecPatIn name -- record
66 [(name, InPat name, Bool)] -- True <=> source used punning
69 = WildPat Type -- wild card
71 | VarPat id -- variable (type is in the Id)
73 | LazyPat (OutPat id) -- lazy pattern
75 | AsPat id -- as pattern
78 | ListPat -- syntactic list
79 Type -- the type of the elements
82 | TuplePat [OutPat id] -- tuple
84 -- UnitPat is TuplePat []
87 Type -- the type of the pattern
88 [TyVar] -- Existentially bound type variables
89 [id] -- Ditto dictionaries
92 -- ConOpPats are only used on the input side
94 | RecPat DataCon -- record constructor
95 Type -- the type of the pattern
96 [TyVar] -- Existentially bound type variables
97 [id] -- Ditto dictionaries
98 [(Id, OutPat id, Bool)] -- True <=> source used punning
100 | LitPat -- Used for *non-overloaded* literal patterns:
101 -- Int#, Char#, Int, Char, String, etc.
103 Type -- type of pattern
105 | NPat -- Used for *overloaded* literal patterns
106 HsLit -- the literal is retained so that
107 -- the desugarer can readily identify
108 -- equations with identical literal-patterns
109 Type -- type of pattern, t
110 (HsExpr id (OutPat id))
111 -- of type t -> Bool; detects match
114 HsLit -- Same reason as for LitPat
115 -- (This could be an Integer, but then
116 -- it's harder to partitionEqnsByLit
117 -- in the desugarer.)
118 Type -- Type of pattern, t
119 (HsExpr id (OutPat id)) -- Of type t -> Bool; detects match
120 (HsExpr id (OutPat id)) -- Of type t -> t; subtracts k
122 | DictPat -- Used when destructing Dictionaries with an explicit case
123 [id] -- superclass dicts
127 Now name in Inpat is not need to be in NAmedThing to be Outputable.
128 Needed by ../deSugar/Check.lhs
133 instance (Outputable name) => Outputable (InPat name) where
136 pprInPat :: (Outputable name) => InPat name -> SDoc
138 pprInPat (WildPatIn) = char '_'
139 pprInPat (VarPatIn var) = ppr var
140 pprInPat (LitPatIn s) = ppr s
141 pprInPat (SigPatIn pat ty) = ppr pat <+> dcolon <+> ppr ty
142 pprInPat (LazyPatIn pat) = char '~' <> ppr pat
143 pprInPat (AsPatIn name pat) = parens (hcat [ppr name, char '@', ppr pat])
145 pprInPat (ConPatIn c pats)
147 | otherwise = hsep [ppr c, interppSP pats] -- ParPats put in the parens
149 pprInPat (ConOpPatIn pat1 op fixity pat2)
150 = hsep [ppr pat1, ppr op, ppr pat2] -- ParPats put in parens
152 -- ToDo: use pprSym to print op (but this involves fiddling various
153 -- contexts & I'm lazy...); *PatIns are *rarely* printed anyway... (WDP)
155 pprInPat (NegPatIn pat)
157 pp_pat = pprInPat pat
165 pprInPat (ParPatIn pat)
166 = parens (pprInPat pat)
168 pprInPat (ListPatIn pats)
169 = brackets (interpp'SP pats)
170 pprInPat (TuplePatIn pats False)
171 = text "(#" <> (interpp'SP pats) <> text "#)"
172 pprInPat (TuplePatIn pats True)
173 = parens (interpp'SP pats)
174 pprInPat (NPlusKPatIn n k)
175 = parens (hcat [ppr n, char '+', ppr k])
177 pprInPat (RecPatIn con rpats)
178 = hsep [ppr con, braces (hsep (punctuate comma (map (pp_rpat) rpats)))]
180 pp_rpat (v, _, True) = ppr v
181 pp_rpat (v, p, _) = hsep [ppr v, char '=', ppr p]
185 instance (Outputable id) => Outputable (OutPat id) where
190 pprOutPat (WildPat ty) = char '_'
191 pprOutPat (VarPat var) = ppr var
192 pprOutPat (LazyPat pat) = hcat [char '~', ppr pat]
193 pprOutPat (AsPat name pat)
194 = parens (hcat [ppr name, char '@', ppr pat])
196 pprOutPat (ConPat name ty [] [] [])
199 pprOutPat (ConPat name ty tyvars dicts pats)
200 = parens (hsep [ppr name, interppSP tyvars, interppSP dicts, interppSP pats])
202 pprOutPat (ListPat ty pats)
203 = brackets (interpp'SP pats)
204 pprOutPat (TuplePat pats boxed@True)
205 = parens (interpp'SP pats)
206 pprOutPat (TuplePat pats unboxed@False)
207 = text "(#" <> (interpp'SP pats) <> text "#)"
209 pprOutPat (RecPat con ty tvs dicts rpats)
210 = hsep [ppr con, interppSP tvs, interppSP dicts, braces (hsep (punctuate comma (map (pp_rpat) rpats)))]
212 pp_rpat (v, _, True) = ppr v
213 pp_rpat (v, p, _) = hsep [ppr v, char '=', ppr p]
215 pprOutPat (LitPat l ty) = ppr l -- ToDo: print more
216 pprOutPat (NPat l ty e) = ppr l -- ToDo: print more
217 pprOutPat (NPlusKPat n k ty e1 e2) -- ToDo: print more
218 = parens (hcat [ppr n, char '+', ppr k])
220 pprOutPat (DictPat dicts methods)
221 = parens (sep [ptext SLIT("{-dict-}"),
222 brackets (interpp'SP dicts),
223 brackets (interpp'SP methods)])
227 %************************************************************************
229 %* predicates for checking things about pattern-lists in EquationInfo *
231 %************************************************************************
232 \subsection[Pat-list-predicates]{Look for interesting things in patterns}
234 Unlike in the Wadler chapter, where patterns are either ``variables''
235 or ``constructors,'' here we distinguish between:
238 Patterns that cannot fail to match: variables, wildcards, and lazy
241 These are the irrefutable patterns; the two other categories
242 are refutable patterns.
245 A non-literal constructor pattern (see next category).
247 \item[literal patterns:]
248 At least the numeric ones may be overloaded.
251 A pattern is in {\em exactly one} of the above three categories; `as'
252 patterns are treated specially, of course.
254 The 1.3 report defines what ``irrefutable'' and ``failure-free'' patterns are.
256 irrefutablePats :: [OutPat id] -> Bool
257 irrefutablePats pat_list = all irrefutablePat pat_list
259 irrefutablePat (AsPat _ pat) = irrefutablePat pat
260 irrefutablePat (WildPat _) = True
261 irrefutablePat (VarPat _) = True
262 irrefutablePat (LazyPat _) = True
263 irrefutablePat (DictPat ds ms) = (length ds + length ms) <= 1
264 irrefutablePat other = False
266 failureFreePat :: OutPat id -> Bool
268 failureFreePat (WildPat _) = True
269 failureFreePat (VarPat _) = True
270 failureFreePat (LazyPat _) = True
271 failureFreePat (AsPat _ pat) = failureFreePat pat
272 failureFreePat (ConPat con tys _ _ pats) = only_con con && all failureFreePat pats
273 failureFreePat (RecPat con _ _ _ fields) = only_con con && and [ failureFreePat pat | (_,pat,_) <- fields ]
274 failureFreePat (ListPat _ _) = False
275 failureFreePat (TuplePat pats _) = all failureFreePat pats
276 failureFreePat (DictPat _ _) = True
277 failureFreePat other_pat = False -- Literals, NPat
279 only_con con = maybeToBool (maybeTyConSingleCon (dataConTyCon con))
283 isWildPat (WildPat _) = True
284 isWildPat other = False
286 patsAreAllCons :: [OutPat id] -> Bool
287 patsAreAllCons pat_list = all isConPat pat_list
289 isConPat (AsPat _ pat) = isConPat pat
290 isConPat (ConPat _ _ _ _ _) = True
291 isConPat (ListPat _ _) = True
292 isConPat (TuplePat _ _) = True
293 isConPat (RecPat _ _ _ _ _) = True
294 isConPat (DictPat ds ms) = (length ds + length ms) > 1
295 isConPat other = False
297 patsAreAllLits :: [OutPat id] -> Bool
298 patsAreAllLits pat_list = all isLitPat pat_list
300 isLitPat (AsPat _ pat) = isLitPat pat
301 isLitPat (LitPat _ _) = True
302 isLitPat (NPat _ _ _) = True
303 isLitPat (NPlusKPat _ _ _ _ _) = True
304 isLitPat other = False
307 This function @collectPatBinders@ works with the ``collectBinders''
308 functions for @HsBinds@, etc. The order in which the binders are
309 collected is important; see @HsBinds.lhs@.
312 collectPatBinders :: InPat a -> [a]
313 collectPatBinders pat = collect pat []
315 collectPatsBinders :: [InPat a] -> [a]
316 collectPatsBinders pats = foldr collect [] pats
318 collect WildPatIn bndrs = bndrs
319 collect (VarPatIn var) bndrs = var : bndrs
320 collect (LitPatIn _) bndrs = bndrs
321 collect (SigPatIn pat _) bndrs = collect pat bndrs
322 collect (LazyPatIn pat) bndrs = collect pat bndrs
323 collect (AsPatIn a pat) bndrs = a : collect pat bndrs
324 collect (NPlusKPatIn n _) bndrs = n : bndrs
325 collect (ConPatIn c pats) bndrs = foldr collect bndrs pats
326 collect (ConOpPatIn p1 c f p2) bndrs = collect p1 (collect p2 bndrs)
327 collect (NegPatIn pat) bndrs = collect pat bndrs
328 collect (ParPatIn pat) bndrs = collect pat bndrs
329 collect (ListPatIn pats) bndrs = foldr collect bndrs pats
330 collect (TuplePatIn pats _) bndrs = foldr collect bndrs pats
331 collect (RecPatIn c fields) bndrs = foldr (\ (f,pat,_) bndrs -> collect pat bndrs) bndrs fields