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