[project @ 2001-11-26 09:20:25 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, 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 _ (TuplePatIn pats boxed) = TuplePatIn (map untidy_no_pars pats) boxed
146
147 untidy _ pat = pprPanic "Check.untidy: SigPatIn" (ppr pat)
148
149 pars :: NeedPars -> WarningPat -> WarningPat
150 pars True p = ParPatIn p
151 pars _    p = p
152
153 untidy_lit :: HsLit -> HsLit
154 untidy_lit (HsCharPrim c) = HsChar c
155 --untidy_lit (HsStringPrim s) = HsString s
156 untidy_lit lit = lit
157 \end{code}
158
159 This equation is the same that check, the only difference is that the
160 boring work is done, that work needs to be done only once, this is
161 the reason top have two functions, check is the external interface,
162 @check'@ is called recursively.
163
164 There are several cases:
165
166 \begin{itemize} 
167 \item There are no equations: Everything is OK. 
168 \item There are only one equation, that can fail, and all the patterns are
169       variables. Then that equation is used and the same equation is 
170       non-exhaustive.
171 \item All the patterns are variables, and the match can fail, there are 
172       more equations then the results is the result of the rest of equations 
173       and this equation is used also.
174
175 \item The general case, if all the patterns are variables (here the match 
176       can't fail) then the result is that this equation is used and this 
177       equation doesn't generate non-exhaustive cases.
178
179 \item In the general case, there can exist literals ,constructors or only 
180       vars in the first column, we actuate in consequence.
181
182 \end{itemize}
183
184
185 \begin{code}
186
187 check' :: [EquationInfo] -> ([ExhaustivePat],EqnSet)  
188 check' []                                              = ([([],[])],emptyUniqSet)
189
190 check' [EqnInfo n ctx ps (MatchResult CanFail _)] 
191    | all_vars ps  = ([(takeList ps (repeat new_wild_pat),[])],  unitUniqSet n)
192
193 check' qs@((EqnInfo n ctx ps (MatchResult CanFail _)):rs)
194    | all_vars ps  = (pats,  addOneToUniqSet indexs n)
195   where
196     (pats,indexs) = check' rs
197
198 check' qs@((EqnInfo n ctx ps result):_) 
199    | all_vars ps  = ([],  unitUniqSet n)
200 --   | nplusk       = panic "Check.check': Work in progress: nplusk"
201 --   | npat         = panic "Check.check': Work in progress: npat ?????"
202    | literals     = split_by_literals qs
203    | constructors = split_by_constructor qs
204    | only_vars    = first_column_only_vars qs
205    | otherwise    = panic "Check.check': Not implemented :-("
206   where
207      -- Note: RecPats will have been simplified to ConPats
208      --       at this stage.
209     constructors = or (map is_con qs)
210     literals     = or (map is_lit qs)    
211     only_vars    = and (map is_var qs) 
212 --    npat         = or (map is_npat qs)
213 --    nplusk       = or (map is_nplusk qs)
214 \end{code}
215
216 Here begins the code to deal with literals, we need to split the matrix
217 in different matrix beginning by each literal and a last matrix with the 
218 rest of values.
219
220 \begin{code}
221 split_by_literals :: [EquationInfo] -> ([ExhaustivePat],EqnSet)
222 split_by_literals qs = process_literals used_lits qs
223            where
224              used_lits = get_used_lits qs
225 \end{code}
226
227 @process_explicit_literals@ is a function that process each literal that appears 
228 in the column of the matrix. 
229
230 \begin{code}
231 process_explicit_literals :: [HsLit] -> [EquationInfo] -> ([ExhaustivePat],EqnSet)
232 process_explicit_literals lits qs = (concat pats, unionManyUniqSets indexs)
233     where                  
234       pats_indexs   = map (\x -> construct_literal_matrix x qs) lits
235       (pats,indexs) = unzip pats_indexs 
236
237 \end{code}
238
239
240 @process_literals@ calls @process_explicit_literals@ to deal with the literals 
241 that appears in the matrix and deal also with the rest of the cases. It 
242 must be one Variable to be complete.
243
244 \begin{code}
245
246 process_literals :: [HsLit] -> [EquationInfo] -> ([ExhaustivePat],EqnSet)
247 process_literals used_lits qs 
248   | null default_eqns  = ([make_row_vars used_lits (head qs)]++pats,indexs)
249   | otherwise          = (pats_default,indexs_default)
250      where
251        (pats,indexs)   = process_explicit_literals used_lits qs
252        default_eqns    = (map remove_var (filter is_var qs))
253        (pats',indexs') = check' default_eqns 
254        pats_default    = [(new_wild_pat:ps,constraints) | (ps,constraints) <- (pats')] ++ pats 
255        indexs_default  = unionUniqSets indexs' indexs
256 \end{code}
257
258 Here we have selected the literal and we will select all the equations that 
259 begins for that literal and create a new matrix.
260
261 \begin{code}
262 construct_literal_matrix :: HsLit -> [EquationInfo] -> ([ExhaustivePat],EqnSet)
263 construct_literal_matrix lit qs =
264     (map (\ (xs,ys) -> (new_lit:xs,ys)) pats,indexs) 
265   where
266     (pats,indexs) = (check' (remove_first_column_lit lit qs)) 
267     new_lit = LitPatIn lit 
268
269 remove_first_column_lit :: HsLit
270                         -> [EquationInfo] 
271                         -> [EquationInfo]
272 remove_first_column_lit lit qs = 
273     map shift_pat (filter (is_var_lit lit) qs)
274   where
275      shift_pat (EqnInfo n ctx []     result) =  panic "Check.shift_var: no patterns"
276      shift_pat (EqnInfo n ctx (_:ps) result) =  EqnInfo n ctx ps result
277
278 \end{code}
279
280 This function splits the equations @qs@ in groups that deal with the 
281 same constructor.
282
283 \begin{code}
284
285 split_by_constructor :: [EquationInfo] -> ([ExhaustivePat],EqnSet)
286
287 split_by_constructor qs 
288   | not (null unused_cons) = need_default_case used_cons unused_cons qs 
289   | otherwise              = no_need_default_case used_cons qs 
290                        where 
291                           used_cons   = get_used_cons qs 
292                           unused_cons = get_unused_cons used_cons 
293
294 \end{code}
295
296 The first column of the patterns matrix only have vars, then there is 
297 nothing to do.
298
299 \begin{code}
300 first_column_only_vars :: [EquationInfo] -> ([ExhaustivePat],EqnSet)
301 first_column_only_vars qs = (map (\ (xs,ys) -> (new_wild_pat:xs,ys)) pats,indexs)
302                           where
303                             (pats,indexs) = check' (map remove_var qs)
304        
305 \end{code}
306
307 This equation takes a matrix of patterns and split the equations by 
308 constructor, using all the constructors that appears in the first column 
309 of the pattern matching.
310
311 We can need a default clause or not ...., it depends if we used all the 
312 constructors or not explicitly. The reasoning is similar to @process_literals@,
313 the difference is that here the default case is not always needed.
314
315 \begin{code}
316 no_need_default_case :: [TypecheckedPat] -> [EquationInfo] -> ([ExhaustivePat],EqnSet)
317 no_need_default_case cons qs = (concat pats, unionManyUniqSets indexs)
318     where                  
319       pats_indexs   = map (\x -> construct_matrix x qs) cons
320       (pats,indexs) = unzip pats_indexs 
321
322 need_default_case :: [TypecheckedPat] -> [DataCon] -> [EquationInfo] -> ([ExhaustivePat],EqnSet)
323 need_default_case used_cons unused_cons qs 
324   | null default_eqns  = (pats_default_no_eqns,indexs)
325   | otherwise          = (pats_default,indexs_default)
326      where
327        (pats,indexs)   = no_need_default_case used_cons qs
328        default_eqns    = (map remove_var (filter is_var qs))
329        (pats',indexs') = check' default_eqns 
330        pats_default    = [(make_whole_con c:ps,constraints) | 
331                           c <- unused_cons, (ps,constraints) <- pats'] ++ pats
332        new_wilds       = make_row_vars_for_constructor (head qs)
333        pats_default_no_eqns =  [(make_whole_con c:new_wilds,[]) | c <- unused_cons] ++ pats
334        indexs_default  = unionUniqSets indexs' indexs
335
336 construct_matrix :: TypecheckedPat -> [EquationInfo] -> ([ExhaustivePat],EqnSet)
337 construct_matrix con qs =
338     (map (make_con con) pats,indexs) 
339   where
340     (pats,indexs) = (check' (remove_first_column con qs)) 
341 \end{code}
342
343 Here remove first column is more difficult that with literals due to the fact 
344 that constructors can have arguments.
345
346 For instance, the matrix
347 \begin{verbatim}
348  (: x xs) y
349  z        y
350 \end{verbatim}
351 is transformed in:
352 \begin{verbatim}
353  x xs y
354  _ _  y
355 \end{verbatim}
356
357 \begin{code}
358 remove_first_column :: TypecheckedPat                -- Constructor 
359                     -> [EquationInfo] 
360                     -> [EquationInfo]
361 remove_first_column (ConPat con _ _ _ con_pats) qs = 
362     map shift_var (filter (is_var_con con) qs)
363   where
364      new_wilds = [WildPat (outPatType arg_pat) | arg_pat <- con_pats]
365      shift_var (EqnInfo n ctx (ConPat _ _ _ _ ps':ps) result) = 
366                 EqnInfo n ctx (ps'++ps)               result 
367      shift_var (EqnInfo n ctx (WildPat _     :ps)     result) = 
368                 EqnInfo n ctx (new_wilds ++   ps)     result
369      shift_var _ = panic "Check.Shift_var:No done"
370
371 make_row_vars :: [HsLit] -> EquationInfo -> ExhaustivePat
372 make_row_vars used_lits (EqnInfo _ _ pats _ ) = 
373    (VarPatIn new_var:takeList (tail pats) (repeat new_wild_pat),[(new_var,used_lits)])
374   where new_var = hash_x
375
376 hash_x = mkLocalName unboundKey {- doesn't matter much -}
377                      (mkVarOcc SLIT("#x"))
378                      noSrcLoc
379
380 make_row_vars_for_constructor :: EquationInfo -> [WarningPat]
381 make_row_vars_for_constructor (EqnInfo _ _ pats _ ) = takeList (tail pats) (repeat new_wild_pat)
382
383 compare_cons :: TypecheckedPat -> TypecheckedPat -> Bool
384 compare_cons (ConPat id1 _ _ _ _) (ConPat id2 _ _ _ _) = id1 == id2  
385
386 remove_dups :: [TypecheckedPat] -> [TypecheckedPat]
387 remove_dups []     = []
388 remove_dups (x:xs) | or (map (\y -> compare_cons x y) xs) = remove_dups  xs
389                    | otherwise                            = x : remove_dups xs
390
391 get_used_cons :: [EquationInfo] -> [TypecheckedPat]
392 get_used_cons qs = remove_dups [con | (EqnInfo _ _ (con@(ConPat _ _ _ _ _):_) _) <- qs ]
393
394 remove_dups' :: [HsLit] -> [HsLit] 
395 remove_dups' []                   = []
396 remove_dups' (x:xs) | x `elem` xs = remove_dups' xs
397                     | otherwise   = x : remove_dups' xs 
398
399
400 get_used_lits :: [EquationInfo] -> [HsLit]
401 get_used_lits qs = remove_dups' all_literals
402                  where
403                    all_literals = get_used_lits' qs
404
405 get_used_lits' :: [EquationInfo] -> [HsLit]
406 get_used_lits' [] = []
407 get_used_lits' ((EqnInfo _ _ ((LitPat lit _):_) _):qs) = 
408                lit : get_used_lits qs
409 get_used_lits' ((EqnInfo _ _ ((NPat lit _ _):_) _):qs) = 
410                lit : get_used_lits qs
411 get_used_lits' (q:qs)                                  =       
412                get_used_lits qs
413
414 get_unused_cons :: [TypecheckedPat] -> [DataCon]
415 get_unused_cons used_cons = unused_cons
416      where
417        (ConPat _ ty _ _ _) = head used_cons
418        ty_con              = tcTyConAppTyCon ty         -- Newtype observable
419        all_cons            = tyConDataCons ty_con
420        used_cons_as_id     = map (\ (ConPat d _ _ _ _) -> d) used_cons
421        unused_cons         = uniqSetToList
422                  (mkUniqSet all_cons `minusUniqSet` mkUniqSet used_cons_as_id) 
423
424 all_vars :: [TypecheckedPat] -> Bool
425 all_vars []              = True
426 all_vars (WildPat _:ps)  = all_vars ps
427 all_vars _               = False
428
429 remove_var :: EquationInfo -> EquationInfo
430 remove_var (EqnInfo n ctx (WildPat _:ps) result) = EqnInfo n ctx ps result
431 remove_var _                                     =
432          panic "Check.remove_var: equation does not begin with a variable"
433
434 is_con :: EquationInfo -> Bool
435 is_con (EqnInfo _ _ ((ConPat _ _ _ _ _):_) _) = True
436 is_con _                                      = False
437
438 is_lit :: EquationInfo -> Bool
439 is_lit (EqnInfo _ _ ((LitPat _ _):_) _) = True
440 is_lit (EqnInfo _ _ ((NPat _ _ _):_) _) = True
441 is_lit _                                = False
442
443 is_npat :: EquationInfo -> Bool
444 is_npat (EqnInfo _ _ ((NPat _ _ _):_) _) = True
445 is_npat _                                 = False
446
447 is_nplusk :: EquationInfo -> Bool
448 is_nplusk (EqnInfo _ _ ((NPlusKPat _ _ _ _ _):_) _) = True
449 is_nplusk _                                         = False
450
451 is_var :: EquationInfo -> Bool
452 is_var (EqnInfo _ _ ((WildPat _):_) _)  = True
453 is_var _                                = False
454
455 is_var_con :: DataCon -> EquationInfo -> Bool
456 is_var_con con (EqnInfo _ _ ((WildPat _):_)     _)                 = True
457 is_var_con con (EqnInfo _ _ ((ConPat id _ _ _ _):_) _) | id == con = True
458 is_var_con con _                                                   = False
459
460 is_var_lit :: HsLit -> EquationInfo -> Bool
461 is_var_lit lit (EqnInfo _ _ ((WildPat _):_)     _)               = True
462 is_var_lit lit (EqnInfo _ _ ((LitPat lit' _):_) _) | lit == lit' = True
463 is_var_lit lit (EqnInfo _ _ ((NPat lit' _ _):_) _) | lit == lit' = True
464 is_var_lit lit _                                                 = False
465 \end{code}
466
467 The difference beteewn @make_con@ and @make_whole_con@ is that
468 @make_wole_con@ creates a new constructor with all their arguments, and
469 @make_con@ takes a list of argumntes, creates the contructor getting their
470 arguments from the list. See where \fbox{\ ???\ } are used for details.
471
472 We need to reconstruct the patterns (make the constructors infix and
473 similar) at the same time that we create the constructors.
474
475 You can tell tuple constructors using
476 \begin{verbatim}
477         Id.isTupleCon
478 \end{verbatim}
479 You can see if one constructor is infix with this clearer code :-))))))))))
480 \begin{verbatim}
481         Lex.isLexConSym (Name.occNameString (Name.getOccName con))
482 \end{verbatim}
483
484        Rather clumsy but it works. (Simon Peyton Jones)
485
486
487 We don't mind the @nilDataCon@ because it doesn't change the way to
488 print the messsage, we are searching only for things like: @[1,2,3]@,
489 not @x:xs@ ....
490
491 In @reconstruct_pat@ we want to ``undo'' the work
492 that we have done in @simplify_pat@.
493 In particular:
494 \begin{tabular}{lll}
495         @((,) x y)@   & returns to be & @(x, y)@
496 \\      @((:) x xs)@  & returns to be & @(x:xs)@
497 \\      @(x:(...:[])@ & returns to be & @[x,...]@
498 \end{tabular}
499 %
500 The difficult case is the third one becouse we need to follow all the
501 contructors until the @[]@ to know that we need to use the second case,
502 not the second. \fbox{\ ???\ }
503 %
504 \begin{code}
505 isInfixCon con = isDataSymOcc (getOccName con)
506
507 is_nil (ConPatIn con []) = con == getName nilDataCon
508 is_nil _                 = False
509
510 is_list (ListPatIn _) = True
511 is_list _             = False
512
513 return_list id q = id == consDataCon && (is_nil q || is_list q) 
514
515 make_list p q | is_nil q   = ListPatIn [p]
516 make_list p (ListPatIn ps) = ListPatIn (p:ps)  
517 make_list _ _              = panic "Check.make_list: Invalid argument"
518
519 make_con :: TypecheckedPat -> ExhaustivePat -> ExhaustivePat           
520 make_con (ConPat id _ _ _ _) (p:q:ps, constraints) 
521      | return_list id q = (make_list p q : ps, constraints)
522      | isInfixCon id = ((ConOpPatIn p name fixity q) : ps, constraints) 
523     where name   = getName id
524           fixity = panic "Check.make_con: Guessing fixity"
525
526 make_con (ConPat id _ _ _ pats) (ps,constraints) 
527       | isTupleTyCon tc = (TuplePatIn pats_con (tupleTyConBoxity tc) : rest_pats, constraints) 
528       | otherwise       = (ConPatIn name pats_con                    : rest_pats, constraints)
529     where name      = getName id
530           (pats_con, rest_pats) = splitAtList pats ps
531           tc        = dataConTyCon id
532           
533
534 make_whole_con :: DataCon -> WarningPat
535 make_whole_con con | isInfixCon con = ConOpPatIn new_wild_pat name fixity new_wild_pat
536                    | otherwise      = ConPatIn name pats
537                 where 
538                   fixity = panic "Check.make_whole_con: Guessing fixity"
539                   name   = getName con
540                   arity  = dataConSourceArity con 
541                   pats   = replicate arity new_wild_pat
542
543
544 new_wild_pat :: WarningPat
545 new_wild_pat = WildPatIn
546 \end{code}
547
548 This equation makes the same thing as @tidy@ in @Match.lhs@, the
549 difference is that here we can do all the tidy in one place and in the
550 @Match@ tidy it must be done one column each time due to bookkeeping 
551 constraints.
552
553 \begin{code}
554
555 simplify_eqns :: [EquationInfo] -> [EquationInfo]
556 simplify_eqns []                               = []
557 simplify_eqns ((EqnInfo n ctx pats result):qs) = 
558  (EqnInfo n ctx pats' result) : simplify_eqns qs
559  where
560   pats' = map simplify_pat pats
561
562 simplify_pat :: TypecheckedPat -> TypecheckedPat  
563
564 simplify_pat pat@(WildPat gt) = pat
565 simplify_pat (VarPat id)      = WildPat (idType id) 
566
567 simplify_pat (LazyPat p)      = simplify_pat p
568 simplify_pat (AsPat id p)     = simplify_pat p
569 simplify_pat (SigPat p ty fn) = simplify_pat p  -- I'm not sure this is right
570
571 simplify_pat (ConPat id ty tvs dicts ps) = ConPat id ty tvs dicts (map simplify_pat ps)
572
573 simplify_pat (ListPat ty ps) = foldr (\ x -> \y -> ConPat consDataCon list_ty [] [] [x, y])
574                                      (ConPat nilDataCon list_ty [] [] [])
575                                      (map simplify_pat ps)
576                              where list_ty = mkListTy ty
577
578
579 simplify_pat (TuplePat ps boxity)
580   = ConPat (tupleCon boxity arity)
581            (mkTupleTy boxity arity (map outPatType ps)) [] []
582            (map simplify_pat ps)
583   where
584     arity = length ps
585
586 simplify_pat (RecPat dc ty ex_tvs dicts [])   
587   = ConPat dc ty ex_tvs dicts all_wild_pats
588   where
589     all_wild_pats = map WildPat con_arg_tys
590
591       -- Identical to machinations in Match.tidy1:
592     inst_tys    = tcTyConAppArgs ty     -- Newtype is observable
593     con_arg_tys = dataConArgTys dc (inst_tys ++ mkTyVarTys ex_tvs)
594
595 simplify_pat (RecPat dc ty ex_tvs dicts idps) 
596   = ConPat dc ty ex_tvs dicts pats
597   where
598     pats = map (simplify_pat.snd) all_pats
599
600      -- pad out all the missing fields with WildPats.
601     field_pats = map (\ f -> (getName f, WildPat (panic "simplify_pat(RecPat-2)")))
602                      (dataConFieldLabels dc)
603     all_pats = 
604       foldr
605        ( \ (id,p,_) acc -> insertNm (getName id) p acc)
606        field_pats
607        idps
608        
609     insertNm nm p [] = [(nm,p)]
610     insertNm nm p (x@(n,_):xs)
611       | nm == n    = (nm,p):xs
612       | otherwise  = x : insertNm nm p xs
613
614 simplify_pat pat@(LitPat lit lit_ty)        = tidyLitPat lit pat
615
616 -- unpack string patterns fully, so we can see when they overlap with
617 -- each other, or even explicit lists of Chars.
618 simplify_pat pat@(NPat (HsString s) _ _) = 
619    foldr (\c pat -> ConPat consDataCon stringTy [] [] [mk_char_lit c,pat])
620         (ConPat nilDataCon stringTy [] [] []) (_UNPK_INT_ s)
621   where
622     mk_char_lit c = ConPat charDataCon charTy [] [] 
623                         [LitPat (HsCharPrim c) charPrimTy]
624
625 simplify_pat pat@(NPat lit lit_ty hsexpr) = tidyNPat lit lit_ty pat
626
627 simplify_pat (NPlusKPat id hslit ty hsexpr1 hsexpr2) = 
628      WildPat ty
629    where ty = panic "Check.simplify_pat: Gessing ty"
630
631 simplify_pat (DictPat dicts methods) = 
632     case num_of_d_and_ms of
633        0 -> simplify_pat (TuplePat [] Boxed) 
634        1 -> simplify_pat (head dict_and_method_pats) 
635        _ -> simplify_pat (TuplePat dict_and_method_pats Boxed)
636     where
637        num_of_d_and_ms   = length dicts + length methods
638        dict_and_method_pats = map VarPat (dicts ++ methods)
639 \end{code}