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