[project @ 2000-05-25 12:41:14 by simonpj]
[ghc-hetmet.git] / ghc / compiler / deSugar / Check.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1997-1998
3 %
4 % Author: Juan J. Quintela    <quintela@krilin.dc.fi.udc.es>
5 \section{Module @Check@ in @deSugar@}
6
7 \begin{code}
8
9
10 module Check ( check , ExhaustivePat ) where
11
12
13 import HsSyn            
14 import TcHsSyn          ( TypecheckedPat )
15 import DsHsSyn          ( outPatType ) 
16 import CoreSyn          
17
18 import DsUtils          ( EquationInfo(..),
19                           MatchResult(..),
20                           EqnSet,
21                           CanItFail(..),
22                           tidyLitPat
23                         )
24 import Id               ( idType )
25 import DataCon          ( DataCon, dataConTyCon, dataConArgTys,
26                           dataConSourceArity, dataConFieldLabels )
27 import Name             ( Name, mkLocalName, getOccName, isDataSymOcc, getName, mkSrcVarOcc )
28 import Type             ( Type, splitAlgTyConApp, mkTyVarTys,
29                           splitTyConApp_maybe
30                         )
31 import TysWiredIn       ( nilDataCon, consDataCon, 
32                           mkListTy, mkTupleTy, tupleCon
33                         )
34 import Unique           ( unboundKey )
35 import TyCon            ( tyConDataCons, tupleTyConBoxity, isTupleTyCon )
36 import BasicTypes       ( Boxity(..) )
37 import SrcLoc           ( noSrcLoc )
38 import UniqSet
39 import Outputable
40
41 #include "HsVersions.h"
42 \end{code}
43
44 This module performs checks about if one list of equations are:
45 \begin{itemize}
46 \item Overlapped
47 \item Non exhaustive
48 \end{itemize}
49 To discover that we go through the list of equations in a tree-like fashion.
50
51 If you like theory, a similar algorithm is described in:
52 \begin{quotation}
53         {\em Two Techniques for Compiling Lazy Pattern Matching},
54         Luc Maranguet,
55         INRIA Rocquencourt (RR-2385, 1994)
56 \end{quotation}
57 The algorithm is based on the first technique, but there are some differences:
58 \begin{itemize}
59 \item We don't generate code
60 \item We have constructors and literals (not only literals as in the 
61           article)
62 \item We don't use directions, we must select the columns from 
63           left-to-right
64 \end{itemize}
65 (By the way the second technique is really similar to the one used in 
66  @Match.lhs@ to generate code)
67
68 This function takes the equations of a pattern and returns:
69 \begin{itemize}
70 \item The patterns that are not recognized
71 \item The equations that are not overlapped
72 \end{itemize}
73 It simplify the patterns and then call @check'@ (the same semantics), and it 
74 needs to reconstruct the patterns again ....
75
76 The problem appear with things like:
77 \begin{verbatim}
78   f [x,y]   = ....
79   f (x:xs)  = .....
80 \end{verbatim}
81 We want to put the two patterns with the same syntax, (prefix form) and 
82 then all the constructors are equal:
83 \begin{verbatim}
84   f (: x (: y []))   = ....
85   f (: x xs)         = .....
86 \end{verbatim}
87 (more about that in @simplify_eqns@)
88
89 We would prefer to have a @WarningPat@ of type @String@, but Strings and the 
90 Pretty Printer are not friends.
91
92 We use @InPat@ in @WarningPat@ instead of @OutPat@
93 because we need to print the 
94 warning messages in the same way they are introduced, i.e. if the user 
95 wrote:
96 \begin{verbatim}
97         f [x,y] = ..
98 \end{verbatim}
99 He don't want a warning message written:
100 \begin{verbatim}
101         f (: x (: y [])) ........
102 \end{verbatim}
103 Then we need to use InPats.
104 \begin{quotation}
105      Juan Quintela 5 JUL 1998\\
106           User-friendliness and compiler writers are no friends.
107 \end{quotation}
108 \begin{code}
109
110 type WarningPat = InPat Name
111 type ExhaustivePat = ([WarningPat], [(Name, [HsLit])])
112
113
114 check :: [EquationInfo] -> ([ExhaustivePat],EqnSet)
115 check qs = (untidy_warns, incomplete)
116       where
117         (warns, incomplete) = check' (simplify_eqns qs)
118         untidy_warns = map untidy_exhaustive warns 
119
120 untidy_exhaustive :: ExhaustivePat -> ExhaustivePat
121 untidy_exhaustive ([pat], messages) = 
122                   ([untidy_no_pars pat], map untidy_message messages)
123 untidy_exhaustive (pats, messages) = 
124                   (map untidy_pars pats, map untidy_message messages)
125
126 untidy_message :: (Name, [HsLit]) -> (Name, [HsLit])
127 untidy_message (string, lits) = (string, map untidy_lit lits)
128 \end{code}
129
130 The function @untidy@ does the reverse work of the @simplify_pat@ funcion.
131
132 \begin{code}
133
134 type NeedPars = Bool 
135
136 untidy_no_pars :: WarningPat -> WarningPat
137 untidy_no_pars p = untidy False p
138
139 untidy_pars :: WarningPat -> WarningPat
140 untidy_pars p = untidy True p
141
142 untidy :: NeedPars -> WarningPat -> WarningPat
143 untidy _ p@WildPatIn = p
144 untidy _ p@(VarPatIn name) = p
145 untidy _ (LitPatIn lit) = LitPatIn (untidy_lit lit)
146 untidy _ p@(ConPatIn name []) = p
147 untidy b (ConPatIn name pats)  = 
148        pars b (ConPatIn name (map untidy_pars pats)) 
149 untidy b (ConOpPatIn pat1 name fixity pat2) = 
150        pars b (ConOpPatIn (untidy_pars pat1) name fixity (untidy_pars pat2)) 
151 untidy _ (ListPatIn pats)  = ListPatIn (map untidy_no_pars pats) 
152 untidy _ (TuplePatIn pats boxed) = TuplePatIn (map untidy_no_pars pats) boxed
153
154 untidy _ (SigPatIn pat ty)      = panic "Check.untidy: SigPatIn"
155 untidy _ (LazyPatIn pat)        = panic "Check.untidy: LazyPatIn"
156 untidy _ (AsPatIn name pat)     = panic "Check.untidy: AsPatIn"
157 untidy _ (NPlusKPatIn name lit) = panic "Check.untidy: NPlusKPatIn"
158 untidy _ (NegPatIn ipat)        = panic "Check.untidy: NegPatIn"
159 untidy _ (ParPatIn pat)         = panic "Check.untidy: ParPatIn"
160 untidy _ (RecPatIn name fields) = panic "Check.untidy: RecPatIn"
161
162 pars :: NeedPars -> WarningPat -> WarningPat
163 pars True p = ParPatIn p
164 pars _    p = p
165
166 untidy_lit :: HsLit -> HsLit
167 untidy_lit (HsCharPrim c) = HsChar c
168 --untidy_lit (HsStringPrim s) = HsString s
169 untidy_lit lit = lit
170 \end{code}
171
172 This equation is the same that check, the only difference is that the
173 boring work is done, that work needs to be done only once, this is
174 the reason top have two functions, check is the external interface,
175 @check'@ is called recursively.
176
177 There are several cases:
178
179 \begin{itemize} 
180 \item There are no equations: Everything is OK. 
181 \item There are only one equation, that can fail, and all the patterns are
182       variables. Then that equation is used and the same equation is 
183       non-exhaustive.
184 \item All the patterns are variables, and the match can fail, there are 
185       more equations then the results is the result of the rest of equations 
186       and this equation is used also.
187
188 \item The general case, if all the patterns are variables (here the match 
189       can't fail) then the result is that this equation is used and this 
190       equation doesn't generate non-exhaustive cases.
191
192 \item In the general case, there can exist literals ,constructors or only 
193       vars in the first column, we actuate in consequence.
194
195 \end{itemize}
196
197
198 \begin{code}
199
200 check' :: [EquationInfo] -> ([ExhaustivePat],EqnSet)  
201 check' []                                              = ([([],[])],emptyUniqSet)
202
203 check' [EqnInfo n ctx ps (MatchResult CanFail _)] 
204    | all_vars ps  = ([(take (length ps) (repeat new_wild_pat),[])],  unitUniqSet n)
205
206 check' qs@((EqnInfo n ctx ps (MatchResult CanFail _)):rs)
207    | all_vars ps  = (pats,  addOneToUniqSet indexs n)
208   where
209     (pats,indexs) = check' rs
210
211 check' qs@((EqnInfo n ctx ps result):_) 
212    | all_vars ps  = ([],  unitUniqSet n)
213 --   | nplusk       = panic "Check.check': Work in progress: nplusk"
214 --   | npat         = panic "Check.check': Work in progress: npat ?????"
215    | literals     = split_by_literals qs
216    | constructors = split_by_constructor qs
217    | only_vars    = first_column_only_vars qs
218    | otherwise    = panic "Check.check': Not implemented :-("
219   where
220      -- Note: RecPats will have been simplified to ConPats
221      --       at this stage.
222     constructors = or (map is_con qs)
223     literals     = or (map is_lit qs)    
224     only_vars    = and (map is_var qs) 
225 --    npat         = or (map is_npat qs)
226 --    nplusk       = or (map is_nplusk qs)
227 \end{code}
228
229 Here begins the code to deal with literals, we need to split the matrix
230 in different matrix beginning by each literal and a last matrix with the 
231 rest of values.
232
233 \begin{code}
234 split_by_literals :: [EquationInfo] -> ([ExhaustivePat],EqnSet)
235 split_by_literals qs = process_literals used_lits qs
236            where
237              used_lits = get_used_lits qs
238 \end{code}
239
240 @process_explicit_literals@ is a function that process each literal that appears 
241 in the column of the matrix. 
242
243 \begin{code}
244 process_explicit_literals :: [HsLit] -> [EquationInfo] -> ([ExhaustivePat],EqnSet)
245 process_explicit_literals lits qs = (concat pats, unionManyUniqSets indexs)
246     where                  
247       pats_indexs   = map (\x -> construct_literal_matrix x qs) lits
248       (pats,indexs) = unzip pats_indexs 
249
250 \end{code}
251
252
253 @process_literals@ calls @process_explicit_literals@ to deal with the literals 
254 that appears in the matrix and deal also with the rest of the cases. It 
255 must be one Variable to be complete.
256
257 \begin{code}
258
259 process_literals :: [HsLit] -> [EquationInfo] -> ([ExhaustivePat],EqnSet)
260 process_literals used_lits qs 
261   | length default_eqns == 0 = ([make_row_vars used_lits (head qs)]++pats,indexs)
262   | otherwise                = (pats_default,indexs_default)
263      where
264        (pats,indexs)   = process_explicit_literals used_lits qs
265        default_eqns    = (map remove_var (filter is_var qs))
266        (pats',indexs') = check' default_eqns 
267        pats_default    = [(new_wild_pat:ps,constraints) | (ps,constraints) <- (pats')] ++ pats 
268        indexs_default  = unionUniqSets indexs' indexs
269 \end{code}
270
271 Here we have selected the literal and we will select all the equations that 
272 begins for that literal and create a new matrix.
273
274 \begin{code}
275 construct_literal_matrix :: HsLit -> [EquationInfo] -> ([ExhaustivePat],EqnSet)
276 construct_literal_matrix lit qs =
277     (map (\ (xs,ys) -> (new_lit:xs,ys)) pats,indexs) 
278   where
279     (pats,indexs) = (check' (remove_first_column_lit lit qs)) 
280     new_lit = LitPatIn lit 
281
282 remove_first_column_lit :: HsLit
283                         -> [EquationInfo] 
284                         -> [EquationInfo]
285 remove_first_column_lit lit qs = 
286     map shift_pat (filter (is_var_lit lit) qs)
287   where
288      shift_pat (EqnInfo n ctx []     result) =  panic "Check.shift_var: no patterns"
289      shift_pat (EqnInfo n ctx (_:ps) result) =  EqnInfo n ctx ps result
290
291 \end{code}
292
293 This function splits the equations @qs@ in groups that deal with the 
294 same constructor.
295
296 \begin{code}
297
298 split_by_constructor :: [EquationInfo] -> ([ExhaustivePat],EqnSet)
299
300 split_by_constructor qs | length unused_cons /= 0 = need_default_case used_cons unused_cons qs 
301                         | otherwise               = no_need_default_case used_cons qs 
302                        where 
303                           used_cons   = get_used_cons qs 
304                           unused_cons = get_unused_cons used_cons 
305
306 \end{code}
307
308 The first column of the patterns matrix only have vars, then there is 
309 nothing to do.
310
311 \begin{code}
312 first_column_only_vars :: [EquationInfo] -> ([ExhaustivePat],EqnSet)
313 first_column_only_vars qs = (map (\ (xs,ys) -> (new_wild_pat:xs,ys)) pats,indexs)
314                           where
315                             (pats,indexs) = check' (map remove_var qs)
316        
317 \end{code}
318
319 This equation takes a matrix of patterns and split the equations by 
320 constructor, using all the constructors that appears in the first column 
321 of the pattern matching.
322
323 We can need a default clause or not ...., it depends if we used all the 
324 constructors or not explicitly. The reasoning is similar to @process_literals@,
325 the difference is that here the default case is not always needed.
326
327 \begin{code}
328 no_need_default_case :: [TypecheckedPat] -> [EquationInfo] -> ([ExhaustivePat],EqnSet)
329 no_need_default_case cons qs = (concat pats, unionManyUniqSets indexs)
330     where                  
331       pats_indexs   = map (\x -> construct_matrix x qs) cons
332       (pats,indexs) = unzip pats_indexs 
333
334 need_default_case :: [TypecheckedPat] -> [DataCon] -> [EquationInfo] -> ([ExhaustivePat],EqnSet)
335 need_default_case used_cons unused_cons qs 
336   | length default_eqns == 0 = (pats_default_no_eqns,indexs)
337   | otherwise                = (pats_default,indexs_default)
338      where
339        (pats,indexs)   = no_need_default_case used_cons qs
340        default_eqns    = (map remove_var (filter is_var qs))
341        (pats',indexs') = check' default_eqns 
342        pats_default    = [(make_whole_con c:ps,constraints) | 
343                           c <- unused_cons, (ps,constraints) <- pats'] ++ pats
344        new_wilds       = make_row_vars_for_constructor (head qs)
345        pats_default_no_eqns =  [(make_whole_con c:new_wilds,[]) | c <- unused_cons] ++ pats
346        indexs_default  = unionUniqSets indexs' indexs
347
348 construct_matrix :: TypecheckedPat -> [EquationInfo] -> ([ExhaustivePat],EqnSet)
349 construct_matrix con qs =
350     (map (make_con con) pats,indexs) 
351   where
352     (pats,indexs) = (check' (remove_first_column con qs)) 
353 \end{code}
354
355 Here remove first column is more difficult that with literals due to the fact 
356 that constructors can have arguments.
357
358 For instance, the matrix
359 \begin{verbatim}
360  (: x xs) y
361  z        y
362 \end{verbatim}
363 is transformed in:
364 \begin{verbatim}
365  x xs y
366  _ _  y
367 \end{verbatim}
368
369 \begin{code}
370 remove_first_column :: TypecheckedPat                -- Constructor 
371                     -> [EquationInfo] 
372                     -> [EquationInfo]
373 remove_first_column (ConPat con _ _ _ con_pats) qs = 
374     map shift_var (filter (is_var_con con) qs)
375   where
376      new_wilds = [WildPat (outPatType arg_pat) | arg_pat <- con_pats]
377      shift_var (EqnInfo n ctx (ConPat _ _ _ _ ps':ps) result) = 
378                 EqnInfo n ctx (ps'++ps)               result 
379      shift_var (EqnInfo n ctx (WildPat _     :ps)     result) = 
380                 EqnInfo n ctx (new_wilds ++   ps)     result
381      shift_var _ = panic "Check.Shift_var:No done"
382
383 make_row_vars :: [HsLit] -> EquationInfo -> ExhaustivePat
384 make_row_vars used_lits (EqnInfo _ _ pats _ ) = 
385    (VarPatIn new_var:take (length (tail pats)) (repeat new_wild_pat),[(new_var,used_lits)])
386   where new_var = hash_x
387
388 hash_x = mkLocalName unboundKey {- doesn't matter much -}
389                      (mkSrcVarOcc SLIT("#x"))
390                      noSrcLoc
391
392 make_row_vars_for_constructor :: EquationInfo -> [WarningPat]
393 make_row_vars_for_constructor (EqnInfo _ _ pats _ ) = take (length (tail pats)) (repeat new_wild_pat)
394
395 compare_cons :: TypecheckedPat -> TypecheckedPat -> Bool
396 compare_cons (ConPat id1 _ _ _ _) (ConPat id2 _ _ _ _) = id1 == id2  
397
398 remove_dups :: [TypecheckedPat] -> [TypecheckedPat]
399 remove_dups []     = []
400 remove_dups (x:xs) | or (map (\y -> compare_cons x y) xs) = remove_dups  xs
401                    | otherwise                            = x : remove_dups xs
402
403 get_used_cons :: [EquationInfo] -> [TypecheckedPat]
404 get_used_cons qs = remove_dups [con | (EqnInfo _ _ (con@(ConPat _ _ _ _ _):_) _) <- qs ]
405
406 remove_dups' :: [HsLit] -> [HsLit] 
407 remove_dups' []                   = []
408 remove_dups' (x:xs) | x `elem` xs = remove_dups' xs
409                     | otherwise   = x : remove_dups' xs 
410
411
412 get_used_lits :: [EquationInfo] -> [HsLit]
413 get_used_lits qs = remove_dups' all_literals
414                  where
415                    all_literals = get_used_lits' qs
416
417 get_used_lits' :: [EquationInfo] -> [HsLit]
418 get_used_lits' [] = []
419 get_used_lits' ((EqnInfo _ _ ((LitPat lit _):_) _):qs) = 
420                lit : get_used_lits qs
421 get_used_lits' ((EqnInfo _ _ ((NPat lit _ _):_) _):qs) = 
422                lit : get_used_lits qs
423 get_used_lits' (q:qs)                                  =       
424                get_used_lits qs
425
426 get_unused_cons :: [TypecheckedPat] -> [DataCon]
427 get_unused_cons used_cons = unused_cons
428      where
429        (ConPat _ ty _ _ _) = head used_cons
430        Just (ty_con,_)     = splitTyConApp_maybe ty
431        all_cons            = tyConDataCons ty_con
432        used_cons_as_id     = map (\ (ConPat d _ _ _ _) -> d) used_cons
433        unused_cons         = uniqSetToList
434                  (mkUniqSet all_cons `minusUniqSet` mkUniqSet used_cons_as_id) 
435
436
437 all_vars :: [TypecheckedPat] -> Bool
438 all_vars []              = True
439 all_vars (WildPat _:ps)  = all_vars ps
440 all_vars _               = False
441
442 remove_var :: EquationInfo -> EquationInfo
443 remove_var (EqnInfo n ctx (WildPat _:ps) result) = EqnInfo n ctx ps result
444 remove_var _                                     =
445          panic "Check.remove_var: equation does not begin with a variable"
446
447 is_con :: EquationInfo -> Bool
448 is_con (EqnInfo _ _ ((ConPat _ _ _ _ _):_) _) = True
449 is_con _                                      = False
450
451 is_lit :: EquationInfo -> Bool
452 is_lit (EqnInfo _ _ ((LitPat _ _):_) _) = True
453 is_lit (EqnInfo _ _ ((NPat _ _ _):_) _) = True
454 is_lit _                                = False
455
456 is_npat :: EquationInfo -> Bool
457 is_npat (EqnInfo _ _ ((NPat _ _ _):_) _) = True
458 is_npat _                                 = False
459
460 is_nplusk :: EquationInfo -> Bool
461 is_nplusk (EqnInfo _ _ ((NPlusKPat _ _ _ _ _):_) _) = True
462 is_nplusk _                                         = False
463
464 is_var :: EquationInfo -> Bool
465 is_var (EqnInfo _ _ ((WildPat _):_) _)  = True
466 is_var _                                = False
467
468 is_var_con :: DataCon -> EquationInfo -> Bool
469 is_var_con con (EqnInfo _ _ ((WildPat _):_)     _)                 = True
470 is_var_con con (EqnInfo _ _ ((ConPat id _ _ _ _):_) _) | id == con = True
471 is_var_con con _                                                   = False
472
473 is_var_lit :: HsLit -> EquationInfo -> Bool
474 is_var_lit lit (EqnInfo _ _ ((WildPat _):_)     _)               = True
475 is_var_lit lit (EqnInfo _ _ ((LitPat lit' _):_) _) | lit == lit' = True
476 is_var_lit lit (EqnInfo _ _ ((NPat lit' _ _):_) _) | lit == lit' = True
477 is_var_lit lit _                                                 = False
478 \end{code}
479
480 The difference beteewn @make_con@ and @make_whole_con@ is that
481 @make_wole_con@ creates a new constructor with all their arguments, and
482 @make_con@ takes a list of argumntes, creates the contructor getting their
483 arguments from the list. See where \fbox{\ ???\ } are used for details.
484
485 We need to reconstruct the patterns (make the constructors infix and
486 similar) at the same time that we create the constructors.
487
488 You can tell tuple constructors using
489 \begin{verbatim}
490         Id.isTupleCon
491 \end{verbatim}
492 You can see if one constructor is infix with this clearer code :-))))))))))
493 \begin{verbatim}
494         Lex.isLexConSym (Name.occNameString (Name.getOccName con))
495 \end{verbatim}
496
497        Rather clumsy but it works. (Simon Peyton Jones)
498
499
500 We don't mind the @nilDataCon@ because it doesn't change the way to
501 print the messsage, we are searching only for things like: @[1,2,3]@,
502 not @x:xs@ ....
503
504 In @reconstruct_pat@ we want to ``undo'' the work
505 that we have done in @simplify_pat@.
506 In particular:
507 \begin{tabular}{lll}
508         @((,) x y)@   & returns to be & @(x, y)@
509 \\      @((:) x xs)@  & returns to be & @(x:xs)@
510 \\      @(x:(...:[])@ & returns to be & @[x,...]@
511 \end{tabular}
512 %
513 The difficult case is the third one becouse we need to follow all the
514 contructors until the @[]@ to know that we need to use the second case,
515 not the second. \fbox{\ ???\ }
516 %
517 \begin{code}
518 isInfixCon con = isDataSymOcc (getOccName con)
519
520 is_nil (ConPatIn con []) = con == getName nilDataCon
521 is_nil _                 = False
522
523 is_list (ListPatIn _) = True
524 is_list _             = False
525
526 return_list id q = id == consDataCon && (is_nil q || is_list q) 
527
528 make_list p q | is_nil q   = ListPatIn [p]
529 make_list p (ListPatIn ps) = ListPatIn (p:ps)  
530 make_list _ _              = panic "Check.make_list: Invalid argument"
531
532 make_con :: TypecheckedPat -> ExhaustivePat -> ExhaustivePat           
533 make_con (ConPat id _ _ _ _) (p:q:ps, constraints) 
534      | return_list id q = (make_list p q : ps, constraints)
535      | isInfixCon id = ((ConOpPatIn p name fixity q) : ps, constraints) 
536     where name   = getName id
537           fixity = panic "Check.make_con: Guessing fixity"
538
539 make_con (ConPat id _ _ _ pats) (ps,constraints) 
540       | isTupleTyCon tc = (TuplePatIn pats_con (tupleTyConBoxity tc) : rest_pats, constraints) 
541       | otherwise       = (ConPatIn name pats_con                    : rest_pats, constraints)
542     where num_args  = length pats
543           name      = getName id
544           pats_con  = take num_args ps
545           rest_pats = drop num_args ps
546           tc        = dataConTyCon id
547           
548
549 make_whole_con :: DataCon -> WarningPat
550 make_whole_con con | isInfixCon con = ConOpPatIn new_wild_pat name fixity new_wild_pat
551                    | otherwise      = ConPatIn name pats
552                 where 
553                   fixity = panic "Check.make_whole_con: Guessing fixity"
554                   name   = getName con
555                   arity  = dataConSourceArity con 
556                   pats   = take arity (repeat new_wild_pat)
557
558
559 new_wild_pat :: WarningPat
560 new_wild_pat = WildPatIn
561 \end{code}
562
563 This equation makes the same thing as @tidy@ in @Match.lhs@, the
564 difference is that here we can do all the tidy in one place and in the
565 @Match@ tidy it must be done one column each time due to bookkeeping 
566 constraints.
567
568 \begin{code}
569
570 simplify_eqns :: [EquationInfo] -> [EquationInfo]
571 simplify_eqns []                               = []
572 simplify_eqns ((EqnInfo n ctx pats result):qs) = 
573  (EqnInfo n ctx pats' result) : simplify_eqns qs
574  where
575   pats' = map simplify_pat pats
576
577 simplify_pat :: TypecheckedPat -> TypecheckedPat  
578
579 simplify_pat pat@(WildPat gt) = pat
580 simplify_pat (VarPat id)      = WildPat (idType id) 
581
582 simplify_pat (LazyPat p)    = simplify_pat p
583 simplify_pat (AsPat id p)   = simplify_pat p
584
585 simplify_pat (ConPat id ty tvs dicts ps) = ConPat id ty tvs dicts (map simplify_pat ps)
586
587 simplify_pat (ListPat ty ps) = foldr (\ x -> \y -> ConPat consDataCon list_ty [] [] [x, y])
588                                      (ConPat nilDataCon list_ty [] [] [])
589                                      (map simplify_pat ps)
590                              where list_ty = mkListTy ty
591
592
593 simplify_pat (TuplePat ps boxity)
594   = ConPat (tupleCon boxity arity)
595            (mkTupleTy boxity arity (map outPatType ps)) [] []
596            (map simplify_pat ps)
597   where
598     arity = length ps
599
600 simplify_pat (RecPat dc ty ex_tvs dicts [])   
601   = ConPat dc ty ex_tvs dicts all_wild_pats
602   where
603     all_wild_pats = map WildPat con_arg_tys
604
605       -- identical to machinations in Match.tidy1:
606     (_, inst_tys, _) = splitAlgTyConApp ty
607     con_arg_tys      = dataConArgTys dc (inst_tys ++ mkTyVarTys ex_tvs)
608
609 simplify_pat (RecPat dc ty ex_tvs dicts idps) 
610   = ConPat dc ty ex_tvs dicts pats
611   where
612     pats = map (simplify_pat.snd) all_pats
613
614      -- pad out all the missing fields with WildPats.
615     field_pats = map (\ f -> (getName f, WildPat (panic "simplify_pat(RecPat-2)")))
616                      (dataConFieldLabels dc)
617     all_pats = 
618       foldr
619        ( \ (id,p,_) acc -> insertNm (getName id) p acc)
620        field_pats
621        idps
622        
623     insertNm nm p [] = [(nm,p)]
624     insertNm nm p (x@(n,_):xs)
625       | nm == n    = (nm,p):xs
626       | otherwise  = x : insertNm nm p xs
627
628 simplify_pat pat@(LitPat lit lit_ty)        = tidyLitPat lit lit_ty pat
629 simplify_pat pat@(NPat   lit lit_ty hsexpr) = tidyLitPat lit lit_ty pat
630
631 simplify_pat (NPlusKPat id hslit ty hsexpr1 hsexpr2) = 
632      WildPat ty
633    where ty = panic "Check.simplify_pat: Gessing ty"
634
635 simplify_pat (DictPat dicts methods) = 
636     case num_of_d_and_ms of
637        0 -> simplify_pat (TuplePat [] Boxed) 
638        1 -> simplify_pat (head dict_and_method_pats) 
639        _ -> simplify_pat (TuplePat dict_and_method_pats Boxed)
640     where
641        num_of_d_and_ms   = length dicts + length methods
642        dict_and_method_pats = map VarPat (dicts ++ methods)
643
644 \end{code}