1d9edb8beebcd652c84e8acdc6197fd24d282f4a
[ghc-hetmet.git] / ghc / compiler / typecheck / TcRules.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1993-1998
3 %
4 \section[TcRules]{Typechecking transformation rules}
5
6 \begin{code}
7 module TcRules ( tcRules ) where
8
9 #include "HsVersions.h"
10
11 import HsSyn            ( HsDecl(..), RuleDecl(..), RuleBndr(..), HsTyVar(..) )
12 import HsCore           ( UfRuleBody(..) )
13 import RnHsSyn          ( RenamedHsDecl )
14 import TcHsSyn          ( TypecheckedRuleDecl, mkHsLet )
15 import TcMonad
16 import TcSimplify       ( tcSimplifyToDicts, tcSimplifyAndCheck )
17 import TcType           ( zonkTcTypes, newTyVarTy_OpenKind )
18 import TcIfaceSig       ( tcCoreExpr, tcCoreLamBndrs, tcVar )
19 import TcMonoType       ( tcHsSigType, tcHsTyVar, checkSigTyVars )
20 import TcExpr           ( tcExpr )
21 import TcEnv            ( tcExtendLocalValEnv, newLocalId,
22                           tcExtendTyVarEnv
23                         )
24 import Inst             ( LIE, emptyLIE, plusLIEs, instToId )
25 import Id               ( idType, idName, mkVanillaId )
26 import VarSet
27 import Type             ( tyVarsOfTypes )
28 import Bag              ( bagToList )
29 import Outputable
30 import Util
31 \end{code}
32
33 \begin{code}
34 tcRules :: [RenamedHsDecl] -> TcM s (LIE, [TypecheckedRuleDecl])
35 tcRules decls = mapAndUnzipTc tcRule [rule | RuleD rule <- decls]       `thenTc` \ (lies, rules) ->
36                 returnTc (plusLIEs lies, rules)
37
38 tcRule (IfaceRuleDecl fun (UfRuleBody name vars args rhs) src_loc)
39   = tcAddSrcLoc src_loc                 $
40     tcAddErrCtxt (ruleCtxt name)        $
41     tcVar fun                           `thenTc` \ fun' ->
42     tcCoreLamBndrs vars                 $ \ vars' ->
43     mapTc tcCoreExpr args               `thenTc` \ args' ->
44     tcCoreExpr rhs                      `thenTc` \ rhs' ->
45     returnTc (emptyLIE, IfaceRuleDecl fun' (CoreRuleBody name vars' args' rhs') src_loc)
46
47 tcRule (RuleDecl name sig_tvs vars lhs rhs src_loc)
48   = tcAddSrcLoc src_loc                                 $
49     tcAddErrCtxt (ruleCtxt name)                        $
50     newTyVarTy_OpenKind                                 `thenNF_Tc` \ rule_ty ->
51
52         -- Deal with the tyvars mentioned in signatures
53         -- Yuk to the UserTyVar
54     mapNF_Tc (tcHsTyVar . UserTyVar) sig_tvs            `thenNF_Tc` \ sig_tyvars ->
55     tcExtendTyVarEnv sig_tyvars                 (       
56
57                 -- Ditto forall'd variables
58         mapNF_Tc new_id vars                            `thenNF_Tc` \ ids ->
59         tcExtendLocalValEnv [(idName id, id) | id <- ids]       $
60         
61                 -- Now LHS and RHS
62         tcExpr lhs rule_ty                                      `thenTc` \ (lhs', lhs_lie) ->
63         tcExpr rhs rule_ty                                      `thenTc` \ (rhs', rhs_lie) ->
64         
65         returnTc (ids, lhs', rhs', lhs_lie, rhs_lie)
66     )                                           `thenTc` \ (ids, lhs', rhs', lhs_lie, rhs_lie) ->
67
68                 -- Check that LHS has no overloading at all
69     tcSimplifyToDicts lhs_lie                           `thenTc` \ (lhs_dicts, lhs_binds) ->
70     checkSigTyVars sig_tyvars                           `thenTc_`
71
72         -- Gather the template variables and tyvars
73     let
74         tpl_ids = map instToId (bagToList lhs_dicts) ++ ids
75
76         -- IMPORTANT!  We *quantify* over any dicts that appear in the LHS
77         -- Reason: 
78         --      a) The particular dictionary isn't important, because its value
79         --         depends only on the type
80         --              e.g     gcd Int $fIntegralInt
81         --         Here we'd like to match against (gcd Int any_d) for any 'any_d'
82         --
83         --      b) We'd like to make available the dictionaries bound 
84         --         on the LHS in the RHS, so quantifying over them is good
85         --         See the 'lhs_dicts' in tcSimplifyAndCheck for the RHS
86     in
87
88         -- Gather type variables to quantify over
89     zonkTcTypes (rule_ty : map idType tpl_ids)          `thenNF_Tc` \ zonked_tys ->
90     let
91         tpl_tvs = tyVarsOfTypes zonked_tys
92     in
93
94         -- RHS can be a bit more lenient.  In particular,
95         -- we let constant dictionaries etc float outwards
96     tcSimplifyAndCheck (text "tcRule") tpl_tvs 
97                        lhs_dicts rhs_lie                `thenTc` \ (lie', rhs_binds) ->
98
99     returnTc (lie', RuleDecl    name (varSetElems tpl_tvs)
100                                 (map RuleBndr tpl_ids)  -- yuk
101                                 (mkHsLet lhs_binds lhs')
102                                 (mkHsLet rhs_binds rhs')
103                                 src_loc)
104   where
105     new_id (RuleBndr var)          = newTyVarTy_OpenKind        `thenNF_Tc` \ ty ->
106                                      returnNF_Tc (mkVanillaId var ty)
107     new_id (RuleBndrSig var rn_ty) = tcHsSigType rn_ty  `thenTc` \ ty ->
108                                      returnNF_Tc (mkVanillaId var ty)
109
110 ruleCtxt name = ptext SLIT("When checking the transformation rule") <+> 
111                 doubleQuotes (ptext name)
112 \end{code}