2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 \section[PatSyntax]{Abstract Haskell syntax---patterns}
8 Pat(..), InPat, OutPat, LPat,
10 HsConDetails(..), hsConArgs,
12 mkPrefixConPat, mkCharLitPat, mkNilPat,
15 patsAreAllCons, isConPat, isSigPat,
16 patsAreAllLits, isLitPat
19 #include "HsVersions.h"
22 import {-# SOURCE #-} HsExpr ( HsExpr )
25 import HsBinds ( DictBinds, emptyLHsBinds, pprLHsBinds )
26 import HsLit ( HsLit(HsCharPrim), HsOverLit )
27 import HsTypes ( LHsType, SyntaxName, PostTcType )
28 import BasicTypes ( Boxity, tupleParens )
30 import PprCore ( {- instance OutputableBndr TyVar -} )
31 import TysWiredIn ( nilDataCon, charDataCon, charTy )
33 import DataCon ( DataCon )
36 import SrcLoc ( Located(..), unLoc, noLoc )
41 type InPat id = LPat id -- No 'Out' constructors
42 type OutPat id = LPat id -- No 'In' constructors
44 type LPat id = Located (Pat id)
47 = ------------ Simple patterns ---------------
48 WildPat PostTcType -- Wild card
49 | VarPat id -- Variable
50 | VarPatOut id (DictBinds id) -- Used only for overloaded Ids; the
51 -- bindings give its overloaded instances
52 | LazyPat (LPat id) -- Lazy pattern
53 | AsPat (Located id) (LPat id) -- As pattern
54 | ParPat (LPat id) -- Parenthesised pattern
56 ------------ Lists, tuples, arrays ---------------
57 | ListPat [LPat id] -- Syntactic list
58 PostTcType -- The type of the elements
60 | TuplePat [LPat id] -- Tuple
61 Boxity -- UnitPat is TuplePat []
63 | PArrPat [LPat id] -- Syntactic parallel array
64 PostTcType -- The type of the elements
66 ------------ Constructor patterns ---------------
67 | ConPatIn (Located id)
68 (HsConDetails id (LPat id))
70 | ConPatOut (Located DataCon)
71 [TyVar] -- Existentially bound type variables
72 [id] -- Ditto dictionaries
73 (DictBinds id) -- Bindings involving those dictionaries
74 (HsConDetails id (LPat id))
75 Type -- The type of the pattern
77 ------------ Literal and n+k patterns ---------------
78 | LitPat HsLit -- Used for *non-overloaded* literal patterns:
79 -- Int#, Char#, Int, Char, String, etc.
81 | NPatIn HsOverLit -- Always positive
82 (Maybe SyntaxName) -- Just (Name of 'negate') for negative
83 -- patterns, Nothing otherwise
85 | NPatOut HsLit -- Used for literal patterns where there's an equality function to call
86 -- The literal is retained so that the desugarer can readily identify
87 -- equations with identical literal-patterns
88 -- Always HsInteger, HsRat or HsString.
89 -- *Unlike* NPatIn, for negative literals, the
90 -- literal is acutally negative!
91 Type -- Type of pattern, t
92 (HsExpr id) -- Of type t -> Bool; detects match
94 | NPlusKPatIn (Located id) -- n+k pattern
95 HsOverLit -- It'll always be an HsIntegral
96 SyntaxName -- Name of '-' (see RnEnv.lookupSyntaxName)
98 | NPlusKPatOut (Located id)
100 (HsExpr id) -- Of type t -> Bool; detects match
101 (HsExpr id) -- Of type t -> t; subtracts k
104 ------------ Generics ---------------
105 | TypePat (LHsType id) -- Type pattern for generic definitions
106 -- e.g f{| a+b |} = ...
107 -- These show up only in class declarations,
108 -- and should be a top-level pattern
110 ------------ Pattern type signatures ---------------
111 | SigPatIn (LPat id) -- Pattern with a type signature
114 | SigPatOut (LPat id) -- Pattern with a type signature
117 ------------ Dictionary patterns (translation only) ---------------
118 | DictPat -- Used when destructing Dictionaries with an explicit case
119 [id] -- superclass dicts
123 HsConDetails is use both for patterns and for data type declarations
126 data HsConDetails id arg
127 = PrefixCon [arg] -- C p1 p2 p3
128 | RecCon [(Located id, arg)] -- C { x = p1, y = p2 }
129 | InfixCon arg arg -- p1 `C` p2
131 hsConArgs :: HsConDetails id arg -> [arg]
132 hsConArgs (PrefixCon ps) = ps
133 hsConArgs (RecCon fs) = map snd fs
134 hsConArgs (InfixCon p1 p2) = [p1,p2]
138 %************************************************************************
142 %************************************************************************
145 instance (OutputableBndr name) => Outputable (Pat name) where
148 pprPatBndr :: OutputableBndr name => name -> SDoc
149 pprPatBndr var -- Print with type info if -dppr-debug is on
150 = getPprStyle $ \ sty ->
151 if debugStyle sty then
152 parens (pprBndr LambdaBind var) -- Could pass the site to pprPat
153 -- but is it worth it?
157 pprPat :: (OutputableBndr name) => Pat name -> SDoc
159 pprPat (VarPat var) = pprPatBndr var
160 pprPat (VarPatOut var bs) = parens (pprPatBndr var <+> braces (ppr bs))
161 pprPat (WildPat _) = char '_'
162 pprPat (LazyPat pat) = char '~' <> ppr pat
163 pprPat (AsPat name pat) = parens (hcat [ppr name, char '@', ppr pat])
164 pprPat (ParPat pat) = parens (ppr pat)
166 pprPat (ListPat pats _) = brackets (interpp'SP pats)
167 pprPat (PArrPat pats _) = pabrackets (interpp'SP pats)
168 pprPat (TuplePat pats bx) = tupleParens bx (interpp'SP pats)
170 pprPat (ConPatIn con details) = pprUserCon con details
171 pprPat (ConPatOut con tvs dicts binds details _)
172 = getPprStyle $ \ sty -> -- Tiresome; in TcBinds.tcRhs we print out a
173 if debugStyle sty then -- typechecked Pat in an error message,
174 -- and we want to make sure it prints nicely
175 ppr con <+> sep [ hsep (map pprPatBndr tvs) <+> hsep (map pprPatBndr dicts),
176 pprLHsBinds binds, pprConArgs details]
177 else pprUserCon con details
179 pprPat (LitPat s) = ppr s
180 pprPat (NPatIn l _) = ppr l
181 pprPat (NPatOut l _ _) = ppr l
182 pprPat (NPlusKPatIn n k _) = hcat [ppr n, char '+', ppr k]
183 pprPat (NPlusKPatOut n k _ _) = hcat [ppr n, char '+', integer k]
184 pprPat (TypePat ty) = ptext SLIT("{|") <> ppr ty <> ptext SLIT("|}")
185 pprPat (SigPatIn pat ty) = ppr pat <+> dcolon <+> ppr ty
186 pprPat (SigPatOut pat ty) = ppr pat <+> dcolon <+> ppr ty
187 pprPat (DictPat ds ms) = parens (sep [ptext SLIT("{-dict-}"),
188 brackets (interpp'SP ds),
189 brackets (interpp'SP ms)])
191 pprUserCon c (InfixCon p1 p2) = ppr p1 <+> ppr c <+> ppr p2
192 pprUserCon c details = ppr c <+> pprConArgs details
194 pprConArgs (PrefixCon pats) = interppSP pats
195 pprConArgs (InfixCon p1 p2) = interppSP [p1,p2]
196 pprConArgs (RecCon rpats) = braces (hsep (punctuate comma (map (pp_rpat) rpats)))
198 pp_rpat (v, p) = hsep [ppr v, char '=', ppr p]
201 -- add parallel array brackets around a document
203 pabrackets :: SDoc -> SDoc
204 pabrackets p = ptext SLIT("[:") <> p <> ptext SLIT(":]")
208 %************************************************************************
212 %************************************************************************
215 mkPrefixConPat :: DataCon -> [OutPat id] -> Type -> OutPat id
216 -- Make a vanilla Prefix constructor pattern
217 mkPrefixConPat dc pats ty = noLoc $ ConPatOut (noLoc dc) [] [] emptyLHsBinds (PrefixCon pats) ty
219 mkNilPat :: Type -> OutPat id
220 mkNilPat ty = mkPrefixConPat nilDataCon [] ty
222 mkCharLitPat :: Char -> OutPat id
223 mkCharLitPat c = mkPrefixConPat charDataCon [noLoc $ LitPat (HsCharPrim c)] charTy
227 %************************************************************************
229 %* Predicates for checking things about pattern-lists in EquationInfo *
231 %************************************************************************
233 \subsection[Pat-list-predicates]{Look for interesting things in patterns}
235 Unlike in the Wadler chapter, where patterns are either ``variables''
236 or ``constructors,'' here we distinguish between:
239 Patterns that cannot fail to match: variables, wildcards, and lazy
242 These are the irrefutable patterns; the two other categories
243 are refutable patterns.
246 A non-literal constructor pattern (see next category).
248 \item[literal patterns:]
249 At least the numeric ones may be overloaded.
252 A pattern is in {\em exactly one} of the above three categories; `as'
253 patterns are treated specially, of course.
255 The 1.3 report defines what ``irrefutable'' and ``failure-free'' patterns are.
257 isWildPat (WildPat _) = True
258 isWildPat other = False
260 patsAreAllCons :: [Pat id] -> Bool
261 patsAreAllCons pat_list = all isConPat pat_list
263 isConPat (AsPat _ pat) = isConPat (unLoc pat)
264 isConPat (ConPatIn _ _) = True
265 isConPat (ConPatOut _ _ _ _ _ _) = True
266 isConPat (ListPat _ _) = True
267 isConPat (PArrPat _ _) = True
268 isConPat (TuplePat _ _) = True
269 isConPat (DictPat ds ms) = (length ds + length ms) > 1
270 isConPat other = False
272 isSigPat (SigPatIn _ _) = True
273 isSigPat (SigPatOut _ _) = True
274 isSigPat other = False
276 patsAreAllLits :: [Pat id] -> Bool
277 patsAreAllLits pat_list = all isLitPat pat_list
279 isLitPat (AsPat _ pat) = isLitPat (unLoc pat)
280 isLitPat (LitPat _) = True
281 isLitPat (NPatIn _ _) = True
282 isLitPat (NPatOut _ _ _) = True
283 isLitPat (NPlusKPatIn _ _ _) = True
284 isLitPat (NPlusKPatOut _ _ _ _) = True
285 isLitPat other = False