378726502697d14509ff02bcea337db3617d0c3a
[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         eqn_groups = equivClassesByUniq get_uniq eqns_info
90         get_uniq (EqnInfo { eqn_pats = ConPatOut (L _ data_con) _ _ _ _ _ : _}) = getUnique data_con
91     in
92         -- Now make a case alternative out of each group
93     mappM (match_con vars ty) eqn_groups        `thenDs` \ alts ->
94     returnDs (mkCoAlgCaseMatchResult var ty alts)
95 \end{code}
96
97 And here is the local function that does all the work.  It is
98 more-or-less the @matchCon@/@matchClause@ functions on page~94 in
99 Wadler's chapter in SLPJ.  The function @shift_con_pats@ does what the
100 list comprehension in @matchClause@ (SLPJ, p.~94) does, except things
101 are trickier in real life.  Works for @ConPats@, and we want it to
102 fail catastrophically for anything else (which a list comprehension
103 wouldn't).  Cf.~@shift_lit_pats@ in @MatchLits@.
104
105 \begin{code}
106 match_con vars ty eqns
107   = do  { -- Make new vars for the con arguments; avoid new locals where possible
108           arg_vars <- selectMatchVars (map unLoc arg_pats1) arg_tys
109         ; eqns' <- mapM shift eqns 
110         ; match_result <- match (arg_vars ++ vars) ty eqns'
111         ; return (con, tvs1 ++ dicts1 ++ arg_vars, match_result) }
112   where
113     ConPatOut (L _ con) tvs1 dicts1 _ (PrefixCon arg_pats1) pat_ty = firstPat (head eqns)
114
115     shift eqn@(EqnInfo { eqn_wrap = wrap, 
116                          eqn_pats = ConPatOut _ tvs ds bind (PrefixCon arg_pats) _ : pats })
117         = do { prs <- dsHsNestedBinds bind
118              ; return (eqn { eqn_wrap = wrap . wrapBinds (tvs `zip` tvs1) 
119                                              . wrapBinds (ds  `zip` dicts1)
120                                              . mkDsLet (Rec prs),
121                              eqn_pats = map unLoc arg_pats ++ pats }) }
122
123         -- Get the arg types, which we use to type the new vars
124         -- to match on, from the "outside"; the types of pats1 may 
125         -- be more refined, and hence won't do
126     arg_tys = substTys (zipTopTvSubst (dataConTyVars con) inst_tys)
127                        (dataConOrigArgTys con)
128     inst_tys | isVanillaDataCon con = tcTyConAppArgs pat_ty     -- Newtypes opaque!
129              | otherwise            = mkTyVarTys tvs1
130 \end{code}
131
132 Note [Existentials in shift_con_pat]
133 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
134 Consider
135         data T = forall a. Ord a => T a (a->Int)
136
137         f (T x f) True  = ...expr1...
138         f (T y g) False = ...expr2..
139
140 When we put in the tyvars etc we get
141
142         f (T a (d::Ord a) (x::a) (f::a->Int)) True =  ...expr1...
143         f (T b (e::Ord b) (y::a) (g::a->Int)) True =  ...expr2...
144
145 After desugaring etc we'll get a single case:
146
147         f = \t::T b::Bool -> 
148             case t of
149                T a (d::Ord a) (x::a) (f::a->Int)) ->
150             case b of
151                 True  -> ...expr1...
152                 False -> ...expr2...
153
154 *** We have to substitute [a/b, d/e] in expr2! **
155 Hence
156                 False -> ....((/\b\(e:Ord b).expr2) a d)....
157
158 Originally I tried to use 
159         (\b -> let e = d in expr2) a 
160 to do this substitution.  While this is "correct" in a way, it fails
161 Lint, because e::Ord b but d::Ord a.  
162