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