[project @ 2003-12-10 14:15:16 by simonmar]
[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(..) )
14
15 import DsMonad
16 import DsUtils
17
18 import Id               ( Id )
19 import Subst            ( mkSubst, mkInScopeSet, bindSubst, substExpr )
20 import CoreFVs          ( exprFreeVars )
21 import VarEnv           ( emptySubstEnv )
22 import ListSetOps       ( equivClassesByUniq )
23 import SrcLoc           ( unLoc )
24 import Unique           ( Uniquable(..) )
25 \end{code}
26
27 We are confronted with the first column of patterns in a set of
28 equations, all beginning with constructors from one ``family'' (e.g.,
29 @[]@ and @:@ make up the @List@ ``family'').  We want to generate the
30 alternatives for a @Case@ expression.  There are several choices:
31 \begin{enumerate}
32 \item
33 Generate an alternative for every constructor in the family, whether
34 they are used in this set of equations or not; this is what the Wadler
35 chapter does.
36 \begin{description}
37 \item[Advantages:]
38 (a)~Simple.  (b)~It may also be that large sparsely-used constructor
39 families are mainly handled by the code for literals.
40 \item[Disadvantages:]
41 (a)~Not practical for large sparsely-used constructor families, e.g.,
42 the ASCII character set.  (b)~Have to look up a list of what
43 constructors make up the whole family.
44 \end{description}
45
46 \item
47 Generate an alternative for each constructor used, then add a default
48 alternative in case some constructors in the family weren't used.
49 \begin{description}
50 \item[Advantages:]
51 (a)~Alternatives aren't generated for unused constructors.  (b)~The
52 STG is quite happy with defaults.  (c)~No lookup in an environment needed.
53 \item[Disadvantages:]
54 (a)~A spurious default alternative may be generated.
55 \end{description}
56
57 \item
58 ``Do it right:'' generate an alternative for each constructor used,
59 and add a default alternative if all constructors in the family
60 weren't used.
61 \begin{description}
62 \item[Advantages:]
63 (a)~You will get cases with only one alternative (and no default),
64 which should be amenable to optimisation.  Tuples are a common example.
65 \item[Disadvantages:]
66 (b)~Have to look up constructor families in TDE (as above).
67 \end{description}
68 \end{enumerate}
69
70 We are implementing the ``do-it-right'' option for now.  The arguments
71 to @matchConFamily@ are the same as to @match@; the extra @Int@
72 returned is the number of constructors in the family.
73
74 The function @matchConFamily@ is concerned with this
75 have-we-used-all-the-constructors? question; the local function
76 @match_cons_used@ does all the real work.
77 \begin{code}
78 matchConFamily :: [Id]
79                -> [EquationInfo]
80                -> DsM MatchResult
81
82 matchConFamily (var:vars) eqns_info
83   = let
84         -- Sort into equivalence classes by the unique on the constructor
85         -- All the EqnInfos should start with a ConPat
86         eqn_groups = equivClassesByUniq get_uniq eqns_info
87         get_uniq (EqnInfo _ _ (ConPatOut data_con _ _ _ _ : _) _) = getUnique data_con
88     in
89         -- Now make a case alternative out of each group
90     mappM (match_con vars) eqn_groups   `thenDs` \ alts ->
91
92     returnDs (mkCoAlgCaseMatchResult var alts)
93 \end{code}
94
95 And here is the local function that does all the work.  It is
96 more-or-less the @matchCon@/@matchClause@ functions on page~94 in
97 Wadler's chapter in SLPJ.
98
99 \begin{code}
100 match_con vars (eqn1@(EqnInfo _ _ (ConPatOut data_con (PrefixCon arg_pats) _ ex_tvs ex_dicts : _) _)
101                 : other_eqns)
102   = -- Make new vars for the con arguments; avoid new locals where possible
103     mappM selectMatchVarL arg_pats      `thenDs` \ arg_vars ->
104
105     -- Now do the business to make the alt for _this_ ConPat ...
106     match (arg_vars ++ vars) 
107           (map shift_con_pat (eqn1:other_eqns)) `thenDs` \ match_result ->
108
109     --          [See "notes on do_subst" below this function]
110     -- Make the ex_tvs and ex_dicts line up with those
111     -- in the first pattern.  Remember, they are all guaranteed to be variables
112     let
113         match_result' | null ex_tvs     = match_result
114                       | null other_eqns = match_result
115                       | otherwise       = adjustMatchResult do_subst match_result
116     in
117         
118     returnDs (data_con, ex_tvs ++ ex_dicts ++ arg_vars, match_result')
119   where
120     shift_con_pat :: EquationInfo -> EquationInfo
121     shift_con_pat (EqnInfo n ctx (ConPatOut _ (PrefixCon arg_pats) _ _ _ : pats) match_result)
122       = EqnInfo n ctx (map unLoc arg_pats ++ pats) match_result
123
124     other_pats = [p | EqnInfo _ _ (p:_) _ <- other_eqns]
125
126     var_prs = concat [ (ex_tvs'   `zip` ex_tvs) ++ 
127                        (ex_dicts' `zip` ex_dicts) 
128                      | ConPatOut _ _ _ ex_tvs' ex_dicts' <- other_pats ]
129
130     do_subst e = substExpr subst e
131                where
132                  subst    = foldl (\ s (v', v) -> bindSubst s v' v) in_scope var_prs
133                  in_scope = mkSubst (mkInScopeSet (exprFreeVars e)) emptySubstEnv
134                         -- We put all the free variables of e into the in-scope 
135                         -- set of the substitution, not because it is necessary,
136                         -- but to suppress the warning in Subst.lookupInScope
137                         -- Tiresome, but doing the substitution at all is rare.
138 \end{code}
139
140 Note on @shift_con_pats@ just above: does what the list comprehension in
141 @matchClause@ (SLPJ, p.~94) does, except things are trickier in real
142 life.  Works for @ConPats@, and we want it to fail catastrophically
143 for anything else (which a list comprehension wouldn't).
144 Cf.~@shift_lit_pats@ in @MatchLits@.
145
146
147 Notes on do_subst stuff
148 ~~~~~~~~~~~~~~~~~~~~~~~
149 Consider
150         data T = forall a. Ord a => T a (a->Int)
151
152         f (T x f) True  = ...expr1...
153         f (T y g) False = ...expr2..
154
155 When we put in the tyvars etc we get
156
157         f (T a (d::Ord a) (x::a) (f::a->Int)) True =  ...expr1...
158         f (T b (e::Ord a) (y::a) (g::a->Int)) True =  ...expr2...
159
160 After desugaring etc we'll get a single case:
161
162         f = \t::T b::Bool -> 
163             case t of
164                T a (d::Ord a) (x::a) (f::a->Int)) ->
165             case b of
166                 True  -> ...expr1...
167                 False -> ...expr2...
168
169 *** We have to substitute [a/b, d/e] in expr2! **
170 That is what do_subst is doing.
171
172 Originally I tried to use 
173         (\b -> let e = d in expr2) a 
174 to do this substitution.  While this is "correct" in a way, it fails
175 Lint, because e::Ord b but d::Ord a.  
176
177 So now I simply do the substitution properly using substExpr.
178