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