d115306a3ac8b6abaca844da66f57bbf902d23cf
[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 Maybes           ( maybeToBool )
30 import Outputable       
31 import TyCon            ( maybeTyConSingleCon )
32 import Type             ( Type )
33 \end{code}
34
35 Patterns come in distinct before- and after-typechecking flavo(u)rs.
36 \begin{code}
37 data InPat name
38   = WildPatIn                           -- wild card
39   | VarPatIn        name                -- variable
40   | LitPatIn        HsLit               -- literal
41   | LazyPatIn       (InPat name)        -- lazy pattern
42   | AsPatIn         name                -- as pattern
43                     (InPat name)
44   | SigPatIn        (InPat name)
45                     (HsType name)
46   | ConPatIn        name                -- constructed type
47                     [InPat name]
48   | ConOpPatIn      (InPat name)
49                     name
50                     Fixity              -- c.f. OpApp in HsExpr
51                     (InPat name)
52
53   | NPlusKPatIn     name                --  n+k pattern
54                     HsLit
55
56   -- We preserve prefix negation and parenthesis for the precedence parser.
57
58   | NegPatIn        (InPat name)        -- negated pattern
59   | ParPatIn        (InPat name)        -- parenthesised pattern
60
61   | ListPatIn       [InPat name]        -- syntactic list
62                                         -- must have >= 1 elements
63   | TuplePatIn      [InPat name] Bool   -- tuple (boxed?)
64
65   | RecPatIn        name                -- record
66                     [(name, InPat name, Bool)]  -- True <=> source used punning
67
68 data OutPat id
69   = WildPat         Type        -- wild card
70
71   | VarPat          id                  -- variable (type is in the Id)
72
73   | LazyPat         (OutPat id) -- lazy pattern
74
75   | AsPat           id                  -- as pattern
76                     (OutPat id)
77
78   | ListPat                             -- syntactic list
79                     Type        -- the type of the elements
80                     [OutPat id]
81
82   | TuplePat        [OutPat id] -- tuple
83                     Bool                -- boxed?
84                                                 -- UnitPat is TuplePat []
85
86   | ConPat          DataCon
87                     Type        -- the type of the pattern
88                     [TyVar]     -- Existentially bound type variables
89                     [id]                -- Ditto dictionaries
90                     [OutPat id]
91
92   -- ConOpPats are only used on the input side
93
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
99
100   | LitPat          -- Used for *non-overloaded* literal patterns:
101                     -- Int#, Char#, Int, Char, String, etc.
102                     HsLit
103                     Type        -- type of pattern
104
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
112
113   | NPlusKPat       id
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
121
122   | DictPat         -- Used when destructing Dictionaries with an explicit case
123                     [id]                        -- superclass dicts
124                     [id]                        -- methods
125 \end{code}
126
127 Now name in Inpat is not need to be in NAmedThing to be Outputable.
128 Needed by ../deSugar/Check.lhs
129
130 JJQC-2-12-97
131
132 \begin{code}
133 instance (Outputable name) => Outputable (InPat name) where
134     ppr = pprInPat
135
136 pprInPat :: (Outputable name) => InPat name -> SDoc
137
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])
144
145 pprInPat (ConPatIn c pats)
146   | null pats = ppr c
147   | otherwise = hsep [ppr c, interppSP pats] -- ParPats put in the parens
148
149 pprInPat (ConOpPatIn pat1 op fixity pat2)
150  = hsep [ppr pat1, ppr op, ppr pat2] -- ParPats put in parens
151
152         -- ToDo: use pprSym to print op (but this involves fiddling various
153         -- contexts & I'm lazy...); *PatIns are *rarely* printed anyway... (WDP)
154
155 pprInPat (NegPatIn pat)
156   = let
157         pp_pat = pprInPat pat
158     in
159     char '-' <> (
160     case pat of
161       LitPatIn _ -> pp_pat
162       _          -> parens pp_pat
163     )
164
165 pprInPat (ParPatIn pat)
166   = parens (pprInPat pat)
167
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])
176
177 pprInPat (RecPatIn con rpats)
178   = hsep [ppr con, braces (hsep (punctuate comma (map (pp_rpat) rpats)))]
179   where
180     pp_rpat (v, _, True) = ppr v
181     pp_rpat (v, p, _)    = hsep [ppr v, char '=', ppr p]
182 \end{code}
183
184 \begin{code}
185 instance (Outputable id) => Outputable (OutPat id) where
186     ppr = pprOutPat
187 \end{code}
188
189 \begin{code}
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])
195
196 pprOutPat (ConPat name ty [] [] [])
197   = ppr name
198
199 pprOutPat (ConPat name ty tyvars dicts pats)
200   = parens (hsep [ppr name, interppSP tyvars, interppSP dicts, interppSP pats])
201
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 "#)"
208
209 pprOutPat (RecPat con ty tvs dicts rpats)
210   = hsep [ppr con, interppSP tvs, interppSP dicts, braces (hsep (punctuate comma (map (pp_rpat) rpats)))]
211   where
212     pp_rpat (v, _, True) = ppr v
213     pp_rpat (v, p, _)    = hsep [ppr v, char '=', ppr p]
214
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])
219
220 pprOutPat (DictPat dicts methods)
221  = parens (sep [ptext SLIT("{-dict-}"),
222                   brackets (interpp'SP dicts),
223                   brackets (interpp'SP methods)])
224
225 \end{code}
226
227 %************************************************************************
228 %*                                                                      *
229 %* predicates for checking things about pattern-lists in EquationInfo   *
230 %*                                                                      *
231 %************************************************************************
232 \subsection[Pat-list-predicates]{Look for interesting things in patterns}
233
234 Unlike in the Wadler chapter, where patterns are either ``variables''
235 or ``constructors,'' here we distinguish between:
236 \begin{description}
237 \item[unfailable:]
238 Patterns that cannot fail to match: variables, wildcards, and lazy
239 patterns.
240
241 These are the irrefutable patterns; the two other categories
242 are refutable patterns.
243
244 \item[constructor:]
245 A non-literal constructor pattern (see next category).
246
247 \item[literal patterns:]
248 At least the numeric ones may be overloaded.
249 \end{description}
250
251 A pattern is in {\em exactly one} of the above three categories; `as'
252 patterns are treated specially, of course.
253
254 The 1.3 report defines what ``irrefutable'' and ``failure-free'' patterns are.
255 \begin{code}
256 irrefutablePats :: [OutPat id] -> Bool
257 irrefutablePats pat_list = all irrefutablePat pat_list
258
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
265
266 failureFreePat :: OutPat id -> Bool
267
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
278
279 only_con con = maybeToBool (maybeTyConSingleCon (dataConTyCon con))
280 \end{code}
281
282 \begin{code}
283 isWildPat (WildPat _) = True
284 isWildPat other       = False
285
286 patsAreAllCons :: [OutPat id] -> Bool
287 patsAreAllCons pat_list = all isConPat pat_list
288
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
296
297 patsAreAllLits :: [OutPat id] -> Bool
298 patsAreAllLits pat_list = all isLitPat pat_list
299
300 isLitPat (AsPat _ pat)         = isLitPat pat
301 isLitPat (LitPat _ _)          = True
302 isLitPat (NPat   _ _ _)        = True
303 isLitPat (NPlusKPat _ _ _ _ _) = True
304 isLitPat other                 = False
305 \end{code}
306
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@.
310
311 \begin{code}
312 collectPatBinders :: InPat a -> [a]
313 collectPatBinders pat = collect pat []
314
315 collectPatsBinders :: [InPat a] -> [a]
316 collectPatsBinders pats = foldr collect [] pats
317
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
332 \end{code}