[project @ 2003-02-20 18:18:55 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         Pat(..), InPat, OutPat, 
9         
10         HsConDetails(..), hsConArgs,
11
12         mkPrefixConPat, mkCharLitPat, mkNilPat,
13
14         isWildPat, 
15         patsAreAllCons, isConPat, isSigPat,
16         patsAreAllLits, isLitPat,
17         collectPatBinders, collectPatsBinders,
18         collectSigTysFromPat, collectSigTysFromPats
19     ) where
20
21 #include "HsVersions.h"
22
23
24 import {-# SOURCE #-} HsExpr            ( HsExpr )
25
26 -- friends:
27 import HsLit            ( HsLit(HsCharPrim), HsOverLit )
28 import HsTypes          ( HsType, SyntaxName, PostTcType )
29 import BasicTypes       ( Boxity, tupleParens )
30 -- others:
31 import TysWiredIn       ( nilDataCon, charDataCon, charTy )
32 import Var              ( TyVar )
33 import DataCon          ( DataCon )
34 import Outputable       
35 import Type             ( Type )
36 \end{code}
37
38
39 \begin{code}
40 type InPat id = Pat id          -- No 'Out' constructors
41 type OutPat id = Pat id         -- No 'In' constructors
42
43 data Pat id
44   =     ------------ Simple patterns ---------------
45     WildPat     PostTcType              -- Wild card
46   | VarPat      id                      -- Variable
47   | LazyPat     (Pat id)                -- Lazy pattern
48   | AsPat       id (Pat id)             -- As pattern
49   | ParPat      (Pat id)                -- Parenthesised pattern
50
51         ------------ Lists, tuples, arrays ---------------
52   | ListPat     [Pat id]                -- Syntactic list
53                 PostTcType              -- The type of the elements
54                     
55   | TuplePat    [Pat id]                -- Tuple
56                 Boxity                  -- UnitPat is TuplePat []
57
58   | PArrPat     [Pat id]                -- Syntactic parallel array
59                 PostTcType              -- The type of the elements
60
61         ------------ Constructor patterns ---------------
62   | ConPatIn    id 
63                 (HsConDetails id (Pat id))
64
65   | ConPatOut   DataCon 
66                 (HsConDetails id (Pat id))
67                 Type                    -- The type of the pattern
68                 [TyVar]                 -- Existentially bound type variables
69                 [id]                    -- Ditto dictionaries
70
71         ------------ Literal and n+k patterns ---------------
72   | LitPat          HsLit               -- Used for *non-overloaded* literal patterns:
73                                         -- Int#, Char#, Int, Char, String, etc.
74
75   | NPatIn          HsOverLit           -- Always positive
76                     (Maybe SyntaxName)  -- Just (Name of 'negate') for negative
77                                         -- patterns, Nothing otherwise
78
79   | NPatOut         HsLit               -- Used for literal patterns where there's an equality function to call
80                                         -- The literal is retained so that the desugarer can readily identify
81                                         -- equations with identical literal-patterns
82                                         -- Always HsInteger, HsRat or HsString.
83                                         -- Always HsInteger, HsRat or HsString.
84                                         -- *Unlike* NPatIn, for negative literals, the
85                                         --      literal is acutally negative!
86                     Type                -- Type of pattern, t
87                     (HsExpr id)         -- Of type t -> Bool; detects match
88
89   | NPlusKPatIn     id                  -- n+k pattern
90                     HsOverLit           -- It'll always be an HsIntegral
91                     SyntaxName          -- Name of '-' (see RnEnv.lookupSyntaxName)
92
93   | NPlusKPatOut    id
94                     Integer
95                     (HsExpr id)         -- Of type t -> Bool; detects match
96                     (HsExpr id)         -- Of type t -> t; subtracts k
97
98
99         ------------ Generics ---------------
100   | TypePat         (HsType id)         -- Type pattern for generic definitions
101                                         -- e.g  f{| a+b |} = ...
102                                         -- These show up only in class declarations,
103                                         -- and should be a top-level pattern
104
105         ------------ Pattern type signatures ---------------
106   | SigPatIn        (Pat id)            -- Pattern with a type signature
107                     (HsType id)
108
109   | SigPatOut       (Pat id)            -- Pattern p
110                     Type                -- Type, t, of the whole pattern
111                     (HsExpr id)         -- Coercion function,
112                                         -- of type t -> typeof(p)
113
114         ------------ Dictionary patterns (translation only) ---------------
115   | DictPat         -- Used when destructing Dictionaries with an explicit case
116                     [id]                        -- superclass dicts
117                     [id]                        -- methods
118 \end{code}
119
120 HsConDetails is use both for patterns and for data type declarations
121
122 \begin{code}
123 data HsConDetails id arg
124   = PrefixCon [arg]                     -- C p1 p2 p3
125   | RecCon    [(id, arg)]               -- C { x = p1, y = p2 }
126   | InfixCon  arg arg                   -- p1 `C` p2
127
128 hsConArgs :: HsConDetails id arg -> [arg]
129 hsConArgs (PrefixCon ps)   = ps
130 hsConArgs (RecCon fs)      = map snd fs
131 hsConArgs (InfixCon p1 p2) = [p1,p2]
132 \end{code}
133
134
135 %************************************************************************
136 %*                                                                      *
137 %*              Printing patterns
138 %*                                                                      *
139 %************************************************************************
140
141 \begin{code}
142 instance (OutputableBndr name) => Outputable (Pat name) where
143     ppr = pprPat
144
145 pprPat :: (OutputableBndr name) => Pat name -> SDoc
146
147 pprPat (VarPat var)             -- Print with type info if -dppr-debug is on
148   = getPprStyle $ \ sty ->
149     if debugStyle sty then
150         parens (pprBndr LambdaBind var)         -- Could pass the site to pprPat
151                                                 -- but is it worth it?
152     else
153         ppr var
154
155 pprPat (WildPat _)        = char '_'
156 pprPat (LazyPat pat)      = char '~' <> ppr pat
157 pprPat (AsPat name pat)   = parens (hcat [ppr name, char '@', ppr pat])
158 pprPat (ParPat pat)       = parens (pprPat pat)
159
160 pprPat (ListPat pats _)   = brackets (interpp'SP pats)
161 pprPat (PArrPat pats _)   = pabrackets (interpp'SP pats)
162 pprPat (TuplePat pats bx) = tupleParens bx (interpp'SP pats)
163
164 pprPat (ConPatIn c details)        = pprConPat c details
165 pprPat (ConPatOut c details _ _ _) = pprConPat c details
166
167 pprPat (LitPat s)             = ppr s
168 pprPat (NPatIn l _)           = ppr l
169 pprPat (NPatOut l _ _)        = ppr l
170 pprPat (NPlusKPatIn n k _)    = hcat [ppr n, char '+', ppr k]
171 pprPat (NPlusKPatOut n k _ _) = hcat [ppr n, char '+', integer k]
172
173 pprPat (TypePat ty) = ptext SLIT("{|") <> ppr ty <> ptext SLIT("|}")
174
175 pprPat (SigPatIn pat ty)    = ppr pat <+> dcolon <+> ppr ty
176 pprPat (SigPatOut pat ty _) = ppr pat <+> dcolon <+> ppr ty
177
178 pprPat (DictPat dicts methods)
179  = parens (sep [ptext SLIT("{-dict-}"),
180                   brackets (interpp'SP dicts),
181                   brackets (interpp'SP methods)])
182
183
184
185 pprConPat con (PrefixCon pats)     = ppr con <+> interppSP pats -- inner ParPats supply the necessary parens.
186 pprConPat con (InfixCon pat1 pat2) = hsep [ppr pat1, ppr con, ppr pat2] -- ParPats put in parens
187         -- ToDo: use pprSym to print op (but this involves fiddling various
188         -- contexts & I'm lazy...); *PatIns are *rarely* printed anyway... (WDP)
189 pprConPat con (RecCon rpats)
190   = ppr con <+> braces (hsep (punctuate comma (map (pp_rpat) rpats)))
191   where
192     pp_rpat (v, p) = hsep [ppr v, char '=', ppr p]
193
194
195 -- add parallel array brackets around a document
196 --
197 pabrackets   :: SDoc -> SDoc
198 pabrackets p  = ptext SLIT("[:") <> p <> ptext SLIT(":]")
199 \end{code}
200
201
202 %************************************************************************
203 %*                                                                      *
204 %*              Building patterns
205 %*                                                                      *
206 %************************************************************************
207
208 \begin{code}
209 mkPrefixConPat :: DataCon -> [OutPat id] -> Type -> OutPat id
210 -- Make a vanilla Prefix constructor pattern
211 mkPrefixConPat dc pats ty = ConPatOut dc (PrefixCon pats) ty [] []
212
213 mkNilPat :: Type -> OutPat id
214 mkNilPat ty = mkPrefixConPat nilDataCon [] ty
215
216 mkCharLitPat :: Int -> OutPat id
217 mkCharLitPat c = mkPrefixConPat charDataCon [LitPat (HsCharPrim c)] charTy
218 \end{code}
219
220
221 %************************************************************************
222 %*                                                                      *
223 %* Predicates for checking things about pattern-lists in EquationInfo   *
224 %*                                                                      *
225 %************************************************************************
226
227 \subsection[Pat-list-predicates]{Look for interesting things in patterns}
228
229 Unlike in the Wadler chapter, where patterns are either ``variables''
230 or ``constructors,'' here we distinguish between:
231 \begin{description}
232 \item[unfailable:]
233 Patterns that cannot fail to match: variables, wildcards, and lazy
234 patterns.
235
236 These are the irrefutable patterns; the two other categories
237 are refutable patterns.
238
239 \item[constructor:]
240 A non-literal constructor pattern (see next category).
241
242 \item[literal patterns:]
243 At least the numeric ones may be overloaded.
244 \end{description}
245
246 A pattern is in {\em exactly one} of the above three categories; `as'
247 patterns are treated specially, of course.
248
249 The 1.3 report defines what ``irrefutable'' and ``failure-free'' patterns are.
250 \begin{code}
251 isWildPat (WildPat _) = True
252 isWildPat other       = False
253
254 patsAreAllCons :: [Pat id] -> Bool
255 patsAreAllCons pat_list = all isConPat pat_list
256
257 isConPat (AsPat _ pat)          = isConPat pat
258 isConPat (ConPatIn _ _)         = True
259 isConPat (ConPatOut _ _ _ _ _)  = True
260 isConPat (ListPat _ _)          = True
261 isConPat (PArrPat _ _)          = True
262 isConPat (TuplePat _ _)         = True
263 isConPat (DictPat ds ms)        = (length ds + length ms) > 1
264 isConPat other                  = False
265
266 isSigPat (SigPatIn _ _)    = True
267 isSigPat (SigPatOut _ _ _) = True
268 isSigPat other             = False
269
270 patsAreAllLits :: [Pat id] -> Bool
271 patsAreAllLits pat_list = all isLitPat pat_list
272
273 isLitPat (AsPat _ pat)          = isLitPat pat
274 isLitPat (LitPat _)             = True
275 isLitPat (NPatIn _ _)           = True
276 isLitPat (NPatOut   _ _ _)      = True
277 isLitPat (NPlusKPatIn _ _ _)    = True
278 isLitPat (NPlusKPatOut _ _ _ _) = True
279 isLitPat other                  = False
280 \end{code}
281
282 %************************************************************************
283 %*                                                                      *
284 %*              Gathering stuff out of patterns
285 %*                                                                      *
286 %************************************************************************
287
288 This function @collectPatBinders@ works with the ``collectBinders''
289 functions for @HsBinds@, etc.  The order in which the binders are
290 collected is important; see @HsBinds.lhs@.
291
292 It collects the bounds *value* variables in renamed patterns; type variables
293 are *not* collected.
294
295 \begin{code}
296 collectPatBinders :: Pat a -> [a]
297 collectPatBinders pat = collect pat []
298
299 collectPatsBinders :: [Pat a] -> [a]
300 collectPatsBinders pats = foldr collect [] pats
301
302 collect (WildPat _)              bndrs = bndrs
303 collect (VarPat var)             bndrs = var : bndrs
304 collect (LazyPat pat)            bndrs = collect pat bndrs
305 collect (AsPat a pat)            bndrs = a : collect pat bndrs
306 collect (ParPat  pat)            bndrs = collect pat bndrs
307
308 collect (ListPat pats _)         bndrs = foldr collect bndrs pats
309 collect (PArrPat pats _)         bndrs = foldr collect bndrs pats
310 collect (TuplePat pats _)        bndrs = foldr collect bndrs pats
311
312 collect (ConPatIn c ps)          bndrs = foldr collect bndrs (hsConArgs ps)
313 collect (ConPatOut c ps _ _ ds)  bndrs = ds ++ foldr collect bndrs (hsConArgs ps)
314
315 collect (LitPat _)               bndrs = bndrs
316 collect (NPatIn _ _)             bndrs = bndrs
317 collect (NPatOut _ _ _)          bndrs = bndrs
318
319 collect (NPlusKPatIn n _ _)      bndrs = n : bndrs
320 collect (NPlusKPatOut n _ _ _)   bndrs = n : bndrs
321
322 collect (SigPatIn pat _)         bndrs = collect pat bndrs
323 collect (SigPatOut pat _ _)      bndrs = collect pat bndrs
324 collect (TypePat ty)             bndrs = bndrs
325 collect (DictPat ids1 ids2)      bndrs = ids1 ++ ids2 ++ bndrs
326 \end{code}
327
328 \begin{code}
329 collectSigTysFromPats :: [InPat name] -> [HsType name]
330 collectSigTysFromPats pats = foldr collect_pat [] pats
331
332 collectSigTysFromPat :: InPat name -> [HsType name]
333 collectSigTysFromPat pat = collect_pat pat []
334
335 collect_pat (SigPatIn pat ty)  acc = collect_pat pat (ty:acc)
336 collect_pat (TypePat ty)       acc = ty:acc
337
338 collect_pat (LazyPat pat)      acc = collect_pat pat acc
339 collect_pat (AsPat a pat)      acc = collect_pat pat acc
340 collect_pat (ParPat  pat)      acc = collect_pat pat acc
341 collect_pat (ListPat pats _)   acc = foldr collect_pat acc pats
342 collect_pat (PArrPat pats _)   acc = foldr collect_pat acc pats
343 collect_pat (TuplePat pats _)  acc = foldr collect_pat acc pats
344 collect_pat (ConPatIn c ps)    acc = foldr collect_pat acc (hsConArgs ps)
345 collect_pat other              acc = acc        -- Literals, vars, wildcard
346 \end{code}
347