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