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