2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
5 \section[PatSyntax]{Abstract Haskell syntax---patterns}
8 {-# OPTIONS -fno-warn-incomplete-patterns #-}
9 -- The above warning supression flag is a temporary kludge.
10 -- While working on this module you are encouraged to remove it and fix
11 -- any warnings in the module. See
12 -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
14 {-# LANGUAGE DeriveDataTypeable #-}
17 Pat(..), InPat, OutPat, LPat,
20 HsConPatDetails, hsConPatArgs,
21 HsRecFields(..), HsRecField(..), hsRecFields,
23 mkPrefixConPat, mkCharLitPat, mkNilPat,
25 isBangHsBind, isLiftedPatBind,
26 isBangLPat, hsPatNeedsParens,
32 import {-# SOURCE #-} HsExpr (SyntaxExpr, LHsExpr, pprLExpr)
40 import PprCore ( {- instance OutputableBndr TyVar -} )
50 import Data.Data hiding (TyCon)
56 type InPat id = LPat id -- No 'Out' constructors
57 type OutPat id = LPat id -- No 'In' constructors
59 type LPat id = Located (Pat id)
62 = ------------ Simple patterns ---------------
63 WildPat PostTcType -- Wild card
64 -- The sole reason for a type on a WildPat is to
65 -- support hsPatType :: Pat Id -> Type
67 | VarPat id -- Variable
68 | LazyPat (LPat id) -- Lazy pattern
69 | AsPat (Located id) (LPat id) -- As pattern
70 | ParPat (LPat id) -- Parenthesised pattern
71 | BangPat (LPat id) -- Bang pattern
73 ------------ Lists, tuples, arrays ---------------
74 | ListPat [LPat id] -- Syntactic list
75 PostTcType -- The type of the elements
77 | TuplePat [LPat id] -- Tuple
78 Boxity -- UnitPat is TuplePat []
80 -- You might think that the PostTcType was redundant, but it's essential
83 -- f :: (T a, a) -> Int
85 -- When desugaring, we must generate
86 -- f = /\a. \v::a. case v of (t::T a, w::a) ->
87 -- case t of (T1 (x::Int)) ->
88 -- Note the (w::a), NOT (w::Int), because we have not yet
89 -- refined 'a' to Int. So we must know that the second component
90 -- of the tuple is of type 'a' not Int. See selectMatchVar
92 | PArrPat [LPat id] -- Syntactic parallel array
93 PostTcType -- The type of the elements
95 ------------ Constructor patterns ---------------
96 | ConPatIn (Located id)
100 pat_con :: Located DataCon,
101 pat_tvs :: [TyVar], -- Existentially bound type variables (tyvars only)
102 pat_dicts :: [EvVar], -- Ditto *coercion variables* and *dictionaries*
103 -- One reason for putting coercion variable here, I think,
104 -- is to ensure their kinds are zonked
105 pat_binds :: TcEvBinds, -- Bindings involving those dictionaries
106 pat_args :: HsConPatDetails id,
107 pat_ty :: Type -- The type of the pattern
110 ------------ View patterns ---------------
111 | ViewPat (LHsExpr id)
113 PostTcType -- The overall type of the pattern
114 -- (= the argument type of the view function)
117 ------------ Quasiquoted patterns ---------------
118 -- See Note [Quasi-quote overview] in TcSplice
119 | QuasiQuotePat (HsQuasiQuote id)
121 ------------ Literal and n+k patterns ---------------
122 | LitPat HsLit -- Used for *non-overloaded* literal patterns:
123 -- Int#, Char#, Int, Char, String, etc.
125 | NPat (HsOverLit id) -- ALWAYS positive
126 (Maybe (SyntaxExpr id)) -- Just (Name of 'negate') for negative
127 -- patterns, Nothing otherwise
128 (SyntaxExpr id) -- Equality checker, of type t->t->Bool
130 | NPlusKPat (Located id) -- n+k pattern
131 (HsOverLit id) -- It'll always be an HsIntegral
132 (SyntaxExpr id) -- (>=) function, of type t->t->Bool
133 (SyntaxExpr id) -- Name of '-' (see RnEnv.lookupSyntaxName)
135 ------------ Generics ---------------
136 | TypePat (LHsType id) -- Type pattern for generic definitions
137 -- e.g f{| a+b |} = ...
138 -- These show up only in class declarations,
139 -- and should be a top-level pattern
141 ------------ Pattern type signatures ---------------
142 | SigPatIn (LPat id) -- Pattern with a type signature
145 | SigPatOut (LPat id) -- Pattern with a type signature
148 ------------ Pattern coercions (translation only) ---------------
149 | CoPat HsWrapper -- If co :: t1 ~ t2, p :: t2,
150 -- then (CoPat co p) :: t1
151 (Pat id) -- Why not LPat? Ans: existing locn will do
152 Type -- Type of whole pattern, t1
153 -- During desugaring a (CoPat co pat) turns into a cast with 'co' on
154 -- the scrutinee, followed by a match on 'pat'
155 deriving (Data, Typeable)
158 HsConDetails is use for patterns/expressions *and* for data type declarations
161 data HsConDetails arg rec
162 = PrefixCon [arg] -- C p1 p2 p3
163 | RecCon rec -- C { x = p1, y = p2 }
164 | InfixCon arg arg -- p1 `C` p2
165 deriving (Data, Typeable)
167 type HsConPatDetails id = HsConDetails (LPat id) (HsRecFields id (LPat id))
169 hsConPatArgs :: HsConPatDetails id -> [LPat id]
170 hsConPatArgs (PrefixCon ps) = ps
171 hsConPatArgs (RecCon fs) = map hsRecFieldArg (rec_flds fs)
172 hsConPatArgs (InfixCon p1 p2) = [p1,p2]
175 However HsRecFields is used only for patterns and expressions
176 (not data type declarations)
179 data HsRecFields id arg -- A bunch of record fields
180 -- { x = 3, y = True }
181 -- Used for both expressions and patterns
182 = HsRecFields { rec_flds :: [HsRecField id arg],
183 rec_dotdot :: Maybe Int } -- Note [DotDot fields]
184 deriving (Data, Typeable)
186 -- Note [DotDot fields]
187 -- ~~~~~~~~~~~~~~~~~~~~
188 -- The rec_dotdot field means this:
189 -- Nothing => the normal case
190 -- Just n => the group uses ".." notation,
192 -- In the latter case:
194 -- *before* renamer: rec_flds are exactly the n user-written fields
196 -- *after* renamer: rec_flds includes *all* fields, with
197 -- the first 'n' being the user-written ones
198 -- and the remainder being 'filled in' implicitly
200 data HsRecField id arg = HsRecField {
201 hsRecFieldId :: Located id,
202 hsRecFieldArg :: arg, -- Filled in by renamer
203 hsRecPun :: Bool -- Note [Punning]
204 } deriving (Data, Typeable)
208 -- If you write T { x, y = v+1 }, the HsRecFields will be
209 -- HsRecField x x True ...
210 -- HsRecField y (v+1) False ...
211 -- That is, for "punned" field x is expanded (in the renamer)
212 -- to x=x; but with a punning flag so we can detect it later
213 -- (e.g. when pretty printing)
215 -- If the original field was qualified, we un-qualify it, thus
216 -- T { A.x } means T { A.x = x }
218 hsRecFields :: HsRecFields id arg -> [id]
219 hsRecFields rbinds = map (unLoc . hsRecFieldId) (rec_flds rbinds)
222 %************************************************************************
226 %************************************************************************
229 instance (OutputableBndr name) => Outputable (Pat name) where
232 pprPatBndr :: OutputableBndr name => name -> SDoc
233 pprPatBndr var -- Print with type info if -dppr-debug is on
234 = getPprStyle $ \ sty ->
235 if debugStyle sty then
236 parens (pprBndr LambdaBind var) -- Could pass the site to pprPat
237 -- but is it worth it?
241 pprParendLPat :: (OutputableBndr name) => LPat name -> SDoc
242 pprParendLPat (L _ p) = pprParendPat p
244 pprParendPat :: (OutputableBndr name) => Pat name -> SDoc
245 pprParendPat p | patNeedsParens p = parens (pprPat p)
246 | otherwise = pprPat p
248 patNeedsParens :: Pat name -> Bool
249 patNeedsParens (ConPatIn _ d) = not (null (hsConPatArgs d))
250 patNeedsParens (ConPatOut { pat_args = d }) = not (null (hsConPatArgs d))
251 patNeedsParens (SigPatIn {}) = True
252 patNeedsParens (SigPatOut {}) = True
253 patNeedsParens (ViewPat {}) = True
254 patNeedsParens (CoPat {}) = True
255 patNeedsParens _ = False
257 pprPat :: (OutputableBndr name) => Pat name -> SDoc
258 pprPat (VarPat var) = pprPatBndr var
259 pprPat (WildPat _) = char '_'
260 pprPat (LazyPat pat) = char '~' <> pprParendLPat pat
261 pprPat (BangPat pat) = char '!' <> pprParendLPat pat
262 pprPat (AsPat name pat) = hcat [ppr name, char '@', pprParendLPat pat]
263 pprPat (ViewPat expr pat _) = hcat [pprLExpr expr, text " -> ", ppr pat]
264 pprPat (ParPat pat) = parens (ppr pat)
265 pprPat (ListPat pats _) = brackets (interpp'SP pats)
266 pprPat (PArrPat pats _) = pabrackets (interpp'SP pats)
267 pprPat (TuplePat pats bx _) = tupleParens bx (interpp'SP pats)
269 pprPat (ConPatIn con details) = pprUserCon con details
270 pprPat (ConPatOut { pat_con = con, pat_tvs = tvs, pat_dicts = dicts,
271 pat_binds = binds, pat_args = details })
272 = getPprStyle $ \ sty -> -- Tiresome; in TcBinds.tcRhs we print out a
273 if debugStyle sty then -- typechecked Pat in an error message,
274 -- and we want to make sure it prints nicely
275 ppr con <+> sep [ hsep (map pprPatBndr tvs) <+> hsep (map pprPatBndr dicts),
276 ppr binds, pprConArgs details]
277 else pprUserCon con details
279 pprPat (LitPat s) = ppr s
280 pprPat (NPat l Nothing _) = ppr l
281 pprPat (NPat l (Just _) _) = char '-' <> ppr l
282 pprPat (NPlusKPat n k _ _) = hcat [ppr n, char '+', ppr k]
283 pprPat (QuasiQuotePat qq) = ppr qq
284 pprPat (TypePat ty) = ptext (sLit "{|") <> ppr ty <> ptext (sLit "|}")
285 pprPat (CoPat co pat _) = pprHsWrapper (ppr pat) co
286 pprPat (SigPatIn pat ty) = ppr pat <+> dcolon <+> ppr ty
287 pprPat (SigPatOut pat ty) = ppr pat <+> dcolon <+> ppr ty
289 pprUserCon :: (Outputable con, OutputableBndr id) => con -> HsConPatDetails id -> SDoc
290 pprUserCon c (InfixCon p1 p2) = ppr p1 <+> ppr c <+> ppr p2
291 pprUserCon c details = ppr c <+> pprConArgs details
293 pprConArgs :: OutputableBndr id => HsConPatDetails id -> SDoc
294 pprConArgs (PrefixCon pats) = sep (map pprParendLPat pats)
295 pprConArgs (InfixCon p1 p2) = sep [pprParendLPat p1, pprParendLPat p2]
296 pprConArgs (RecCon rpats) = ppr rpats
298 instance (OutputableBndr id, Outputable arg)
299 => Outputable (HsRecFields id arg) where
300 ppr (HsRecFields { rec_flds = flds, rec_dotdot = Nothing })
301 = braces (fsep (punctuate comma (map ppr flds)))
302 ppr (HsRecFields { rec_flds = flds, rec_dotdot = Just n })
303 = braces (fsep (punctuate comma (map ppr (take n flds) ++ [dotdot])))
305 dotdot = ptext (sLit "..") <+> ifPprDebug (ppr (drop n flds))
307 instance (OutputableBndr id, Outputable arg)
308 => Outputable (HsRecField id arg) where
309 ppr (HsRecField { hsRecFieldId = f, hsRecFieldArg = arg,
311 = ppr f <+> (ppUnless pun $ equals <+> ppr arg)
313 -- add parallel array brackets around a document
315 pabrackets :: SDoc -> SDoc
316 pabrackets p = ptext (sLit "[:") <> p <> ptext (sLit ":]")
320 %************************************************************************
324 %************************************************************************
327 mkPrefixConPat :: DataCon -> [OutPat id] -> Type -> OutPat id
328 -- Make a vanilla Prefix constructor pattern
329 mkPrefixConPat dc pats ty
330 = noLoc $ ConPatOut { pat_con = noLoc dc, pat_tvs = [], pat_dicts = [],
331 pat_binds = emptyTcEvBinds, pat_args = PrefixCon pats,
334 mkNilPat :: Type -> OutPat id
335 mkNilPat ty = mkPrefixConPat nilDataCon [] ty
337 mkCharLitPat :: Char -> OutPat id
338 mkCharLitPat c = mkPrefixConPat charDataCon [noLoc $ LitPat (HsCharPrim c)] charTy
342 %************************************************************************
344 %* Predicates for checking things about pattern-lists in EquationInfo *
346 %************************************************************************
348 \subsection[Pat-list-predicates]{Look for interesting things in patterns}
350 Unlike in the Wadler chapter, where patterns are either ``variables''
351 or ``constructors,'' here we distinguish between:
354 Patterns that cannot fail to match: variables, wildcards, and lazy
357 These are the irrefutable patterns; the two other categories
358 are refutable patterns.
361 A non-literal constructor pattern (see next category).
363 \item[literal patterns:]
364 At least the numeric ones may be overloaded.
367 A pattern is in {\em exactly one} of the above three categories; `as'
368 patterns are treated specially, of course.
370 The 1.3 report defines what ``irrefutable'' and ``failure-free'' patterns are.
372 isBangLPat :: LPat id -> Bool
373 isBangLPat (L _ (BangPat {})) = True
374 isBangLPat (L _ (ParPat p)) = isBangLPat p
377 isBangHsBind :: HsBind id -> Bool
378 -- A pattern binding with an outermost bang
379 -- Defined in this module because HsPat is above HsBinds in the import graph
380 isBangHsBind (PatBind { pat_lhs = p }) = isBangLPat p
381 isBangHsBind _ = False
383 isLiftedPatBind :: HsBind id -> Bool
384 -- A pattern binding with a compound pattern, not just a variable
386 -- (# a, b #) no, even if a::Int#
387 -- x no, even if x::Int#
388 -- We want to warn about a missing bang-pattern on the yes's
389 isLiftedPatBind (PatBind { pat_lhs = p }) = isLiftedLPat p
390 isLiftedPatBind _ = False
392 isLiftedLPat :: LPat id -> Bool
393 isLiftedLPat (L _ (ParPat p)) = isLiftedLPat p
394 isLiftedLPat (L _ (BangPat p)) = isLiftedLPat p
395 isLiftedLPat (L _ (AsPat _ p)) = isLiftedLPat p
396 isLiftedLPat (L _ (TuplePat _ Unboxed _)) = False
397 isLiftedLPat (L _ (VarPat {})) = False
398 isLiftedLPat (L _ (WildPat {})) = False
399 isLiftedLPat _ = True
401 isIrrefutableHsPat :: OutputableBndr id => LPat id -> Bool
402 -- (isIrrefutableHsPat p) is true if matching against p cannot fail,
403 -- in the sense of falling through to the next pattern.
404 -- (NB: this is not quite the same as the (silly) defn
405 -- in 3.17.2 of the Haskell 98 report.)
407 -- isIrrefutableHsPat returns False if it's in doubt; specifically
408 -- on a ConPatIn it doesn't know the size of the constructor family
409 -- But if it returns True, the pattern is definitely irrefutable
410 isIrrefutableHsPat pat
413 go (L _ pat) = go1 pat
415 go1 (WildPat {}) = True
416 go1 (VarPat {}) = True
417 go1 (LazyPat {}) = True
418 go1 (BangPat pat) = go pat
419 go1 (CoPat _ pat _) = go1 pat
420 go1 (ParPat pat) = go pat
421 go1 (AsPat _ pat) = go pat
422 go1 (ViewPat _ pat _) = go pat
423 go1 (SigPatIn pat _) = go pat
424 go1 (SigPatOut pat _) = go pat
425 go1 (TuplePat pats _ _) = all go pats
426 go1 (ListPat {}) = False
427 go1 (PArrPat {}) = False -- ?
429 go1 (ConPatIn {}) = False -- Conservative
430 go1 (ConPatOut{ pat_con = L _ con, pat_args = details })
431 = isJust (tyConSingleDataCon_maybe (dataConTyCon con))
432 -- NB: tyConSingleDataCon_maybe, *not* isProductTyCon, because
433 -- the latter is false of existentials. See Trac #4439
434 && all go (hsConPatArgs details)
436 go1 (LitPat {}) = False
437 go1 (NPat {}) = False
438 go1 (NPlusKPat {}) = False
440 go1 (QuasiQuotePat {}) = urk pat -- Gotten rid of by renamer, before
441 -- isIrrefutablePat is called
442 go1 (TypePat {}) = urk pat
444 urk pat = pprPanic "isIrrefutableHsPat:" (ppr pat)
446 hsPatNeedsParens :: Pat a -> Bool
447 hsPatNeedsParens (WildPat {}) = False
448 hsPatNeedsParens (VarPat {}) = False
449 hsPatNeedsParens (LazyPat {}) = False
450 hsPatNeedsParens (BangPat {}) = False
451 hsPatNeedsParens (CoPat {}) = True
452 hsPatNeedsParens (ParPat {}) = False
453 hsPatNeedsParens (AsPat {}) = False
454 hsPatNeedsParens (ViewPat {}) = True
455 hsPatNeedsParens (SigPatIn {}) = True
456 hsPatNeedsParens (SigPatOut {}) = True
457 hsPatNeedsParens (TuplePat {}) = False
458 hsPatNeedsParens (ListPat {}) = False
459 hsPatNeedsParens (PArrPat {}) = False
460 hsPatNeedsParens (ConPatIn _ ds) = conPatNeedsParens ds
461 hsPatNeedsParens (ConPatOut {}) = True
462 hsPatNeedsParens (LitPat {}) = False
463 hsPatNeedsParens (NPat {}) = False
464 hsPatNeedsParens (NPlusKPat {}) = True
465 hsPatNeedsParens (QuasiQuotePat {}) = True
466 hsPatNeedsParens (TypePat {}) = False
468 conPatNeedsParens :: HsConDetails a b -> Bool
469 conPatNeedsParens (PrefixCon args) = not (null args)
470 conPatNeedsParens (InfixCon {}) = False
471 conPatNeedsParens (RecCon {}) = False