[project @ 2005-03-02 04:35:24 by simonpj]
[ghc-hetmet.git] / ghc / compiler / deSugar / MatchCon.lhs
1
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[MatchCon]{Pattern-matching constructors}
5
6 \begin{code}
7 module MatchCon ( matchConFamily ) where
8
9 #include "HsVersions.h"
10
11 import {-# SOURCE #-} Match     ( match )
12
13 import HsSyn            ( Pat(..), HsConDetails(..), isEmptyLHsBinds )
14 import DsBinds          ( dsHsNestedBinds )
15 import DataCon          ( isVanillaDataCon, dataConTyVars, dataConOrigArgTys )
16 import TcType           ( tcTyConAppArgs )
17 import Type             ( substTys, zipTopTvSubst, mkTyVarTys )
18 import CoreSyn
19 import DsMonad
20 import DsUtils
21
22 import Id               ( Id )
23 import Type             ( Type )
24 import ListSetOps       ( equivClassesByUniq )
25 import SrcLoc           ( unLoc, Located(..) )
26 import Unique           ( Uniquable(..) )
27 import Outputable
28 \end{code}
29
30 We are confronted with the first column of patterns in a set of
31 equations, all beginning with constructors from one ``family'' (e.g.,
32 @[]@ and @:@ make up the @List@ ``family'').  We want to generate the
33 alternatives for a @Case@ expression.  There are several choices:
34 \begin{enumerate}
35 \item
36 Generate an alternative for every constructor in the family, whether
37 they are used in this set of equations or not; this is what the Wadler
38 chapter does.
39 \begin{description}
40 \item[Advantages:]
41 (a)~Simple.  (b)~It may also be that large sparsely-used constructor
42 families are mainly handled by the code for literals.
43 \item[Disadvantages:]
44 (a)~Not practical for large sparsely-used constructor families, e.g.,
45 the ASCII character set.  (b)~Have to look up a list of what
46 constructors make up the whole family.
47 \end{description}
48
49 \item
50 Generate an alternative for each constructor used, then add a default
51 alternative in case some constructors in the family weren't used.
52 \begin{description}
53 \item[Advantages:]
54 (a)~Alternatives aren't generated for unused constructors.  (b)~The
55 STG is quite happy with defaults.  (c)~No lookup in an environment needed.
56 \item[Disadvantages:]
57 (a)~A spurious default alternative may be generated.
58 \end{description}
59
60 \item
61 ``Do it right:'' generate an alternative for each constructor used,
62 and add a default alternative if all constructors in the family
63 weren't used.
64 \begin{description}
65 \item[Advantages:]
66 (a)~You will get cases with only one alternative (and no default),
67 which should be amenable to optimisation.  Tuples are a common example.
68 \item[Disadvantages:]
69 (b)~Have to look up constructor families in TDE (as above).
70 \end{description}
71 \end{enumerate}
72
73 We are implementing the ``do-it-right'' option for now.  The arguments
74 to @matchConFamily@ are the same as to @match@; the extra @Int@
75 returned is the number of constructors in the family.
76
77 The function @matchConFamily@ is concerned with this
78 have-we-used-all-the-constructors? question; the local function
79 @match_cons_used@ does all the real work.
80 \begin{code}
81 matchConFamily :: [Id]
82                -> Type
83                -> [EquationInfo]
84                -> DsM MatchResult
85 matchConFamily (var:vars) ty eqns_info
86   = let
87         -- Sort into equivalence classes by the unique on the constructor
88         -- All the EqnInfos should start with a ConPat
89         groups = equivClassesByUniq get_uniq eqns_info
90         get_uniq (EqnInfo { eqn_pats = ConPatOut (L _ data_con) _ _ _ _ _ : _}) = getUnique data_con
91
92         -- Get the wrapper from the head of each group.  We're going to
93         -- use it as the pattern in this case expression, so we need to 
94         -- ensure that any type variables it mentions in the pattern are
95         -- in scope.  So we put its wrappers outside the case, and
96         -- zap the wrapper for it. 
97         wraps :: [CoreExpr -> CoreExpr]
98         wraps = map (eqn_wrap . head) groups
99
100         groups' = [ eqn { eqn_wrap = idWrapper } : eqns | eqn:eqns <- groups ]
101     in
102         -- Now make a case alternative out of each group
103     mappM (match_con vars ty) groups'   `thenDs` \ alts ->
104     returnDs (adjustMatchResult (foldr (.) idWrapper wraps) $
105               mkCoAlgCaseMatchResult var ty alts)
106 \end{code}
107
108 And here is the local function that does all the work.  It is
109 more-or-less the @matchCon@/@matchClause@ functions on page~94 in
110 Wadler's chapter in SLPJ.  The function @shift_con_pats@ does what the
111 list comprehension in @matchClause@ (SLPJ, p.~94) does, except things
112 are trickier in real life.  Works for @ConPats@, and we want it to
113 fail catastrophically for anything else (which a list comprehension
114 wouldn't).  Cf.~@shift_lit_pats@ in @MatchLits@.
115
116 \begin{code}
117 match_con vars ty eqns
118   = do  { -- Make new vars for the con arguments; avoid new locals where possible
119           arg_vars     <- selectMatchVars (map unLoc arg_pats1) arg_tys
120         ; eqns'        <- mapM shift eqns 
121         ; match_result <- match (arg_vars ++ vars) ty eqns'
122         ; return (con, tvs1 ++ dicts1 ++ arg_vars, match_result) }
123   where
124     ConPatOut (L _ con) tvs1 dicts1 _ (PrefixCon arg_pats1) pat_ty = firstPat (head eqns)
125
126     shift eqn@(EqnInfo { eqn_wrap = wrap, 
127                          eqn_pats = ConPatOut _ tvs ds bind (PrefixCon arg_pats) _ : pats })
128         = do { prs <- dsHsNestedBinds bind
129              ; return (eqn { eqn_wrap = wrap . wrapBinds (tvs `zip` tvs1) 
130                                              . wrapBinds (ds  `zip` dicts1)
131                                              . mkDsLet (Rec prs),
132                              eqn_pats = map unLoc arg_pats ++ pats }) }
133
134         -- Get the arg types, which we use to type the new vars
135         -- to match on, from the "outside"; the types of pats1 may 
136         -- be more refined, and hence won't do
137     arg_tys = substTys (zipTopTvSubst (dataConTyVars con) inst_tys)
138                        (dataConOrigArgTys con)
139     inst_tys | isVanillaDataCon con = tcTyConAppArgs pat_ty     -- Newtypes opaque!
140              | otherwise            = mkTyVarTys tvs1
141 \end{code}
142
143 Note [Existentials in shift_con_pat]
144 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
145 Consider
146         data T = forall a. Ord a => T a (a->Int)
147
148         f (T x f) True  = ...expr1...
149         f (T y g) False = ...expr2..
150
151 When we put in the tyvars etc we get
152
153         f (T a (d::Ord a) (x::a) (f::a->Int)) True =  ...expr1...
154         f (T b (e::Ord b) (y::a) (g::a->Int)) True =  ...expr2...
155
156 After desugaring etc we'll get a single case:
157
158         f = \t::T b::Bool -> 
159             case t of
160                T a (d::Ord a) (x::a) (f::a->Int)) ->
161             case b of
162                 True  -> ...expr1...
163                 False -> ...expr2...
164
165 *** We have to substitute [a/b, d/e] in expr2! **
166 Hence
167                 False -> ....((/\b\(e:Ord b).expr2) a d)....
168
169 Originally I tried to use 
170         (\b -> let e = d in expr2) a 
171 to do this substitution.  While this is "correct" in a way, it fails
172 Lint, because e::Ord b but d::Ord a.  
173