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