{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TypeFamilies #-}
module GHC.Tc.Gen.Rule ( tcRules ) where
import GHC.Prelude
import GHC.Hs
import GHC.Tc.Types
import GHC.Tc.Utils.Monad
import GHC.Tc.Solver
import GHC.Tc.Types.Constraint
import GHC.Core.Predicate
import GHC.Tc.Types.Origin
import GHC.Tc.Utils.TcMType
import GHC.Tc.Utils.TcType
import GHC.Tc.Gen.HsType
import GHC.Tc.Gen.Expr
import GHC.Tc.Utils.Env
import GHC.Tc.Utils.Unify( buildImplicationFor )
import GHC.Tc.Types.Evidence( mkTcCoVarCo )
import GHC.Core.Type
import GHC.Core.TyCon( isTypeFamilyTyCon )
import GHC.Types.Id
import GHC.Types.Var( EvVar )
import GHC.Types.Var.Set
import GHC.Types.Basic ( RuleName )
import GHC.Types.SrcLoc
import GHC.Utils.Outputable
import GHC.Data.FastString
import GHC.Data.Bag
tcRules :: [LRuleDecls GhcRn] -> TcM [LRuleDecls GhcTc]
tcRules :: [LRuleDecls GhcRn] -> TcM [LRuleDecls GhcTc]
tcRules [LRuleDecls GhcRn]
decls = (LRuleDecls GhcRn
-> IOEnv (Env TcGblEnv TcLclEnv) (LRuleDecls GhcTc))
-> [LRuleDecls GhcRn] -> TcM [LRuleDecls GhcTc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((RuleDecls GhcRn -> TcM (RuleDecls GhcTc))
-> LRuleDecls GhcRn
-> IOEnv (Env TcGblEnv TcLclEnv) (LRuleDecls GhcTc)
forall a b. (a -> TcM b) -> Located a -> TcM (Located b)
wrapLocM RuleDecls GhcRn -> TcM (RuleDecls GhcTc)
tcRuleDecls) [LRuleDecls GhcRn]
decls
tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc)
tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc)
tcRuleDecls (HsRules { rds_src :: forall pass. RuleDecls pass -> SourceText
rds_src = SourceText
src
, rds_rules :: forall pass. RuleDecls pass -> [LRuleDecl pass]
rds_rules = [LRuleDecl GhcRn]
decls })
= do { [Located (RuleDecl GhcTc)]
tc_decls <- (LRuleDecl GhcRn
-> IOEnv (Env TcGblEnv TcLclEnv) (Located (RuleDecl GhcTc)))
-> [LRuleDecl GhcRn]
-> IOEnv (Env TcGblEnv TcLclEnv) [Located (RuleDecl GhcTc)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((RuleDecl GhcRn -> TcM (RuleDecl GhcTc))
-> LRuleDecl GhcRn
-> IOEnv (Env TcGblEnv TcLclEnv) (Located (RuleDecl GhcTc))
forall a b. (a -> TcM b) -> Located a -> TcM (Located b)
wrapLocM RuleDecl GhcRn -> TcM (RuleDecl GhcTc)
tcRule) [LRuleDecl GhcRn]
decls
; RuleDecls GhcTc -> TcM (RuleDecls GhcTc)
forall (m :: * -> *) a. Monad m => a -> m a
return (RuleDecls GhcTc -> TcM (RuleDecls GhcTc))
-> RuleDecls GhcTc -> TcM (RuleDecls GhcTc)
forall a b. (a -> b) -> a -> b
$ HsRules :: forall pass.
XCRuleDecls pass
-> SourceText -> [LRuleDecl pass] -> RuleDecls pass
HsRules { rds_ext :: XCRuleDecls GhcTc
rds_ext = NoExtField
XCRuleDecls GhcTc
noExtField
, rds_src :: SourceText
rds_src = SourceText
src
, rds_rules :: [Located (RuleDecl GhcTc)]
rds_rules = [Located (RuleDecl GhcTc)]
tc_decls } }
tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc)
tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc)
tcRule (HsRule { rd_ext :: forall pass. RuleDecl pass -> XHsRule pass
rd_ext = XHsRule GhcRn
ext
, rd_name :: forall pass. RuleDecl pass -> Located (SourceText, RuleName)
rd_name = rname :: Located (SourceText, RuleName)
rname@(L SrcSpan
_ (SourceText
_,RuleName
name))
, rd_act :: forall pass. RuleDecl pass -> Activation
rd_act = Activation
act
, rd_tyvs :: forall pass.
RuleDecl pass -> Maybe [LHsTyVarBndr () (NoGhcTc pass)]
rd_tyvs = Maybe [LHsTyVarBndr () (NoGhcTc GhcRn)]
ty_bndrs
, rd_tmvs :: forall pass. RuleDecl pass -> [LRuleBndr pass]
rd_tmvs = [LRuleBndr GhcRn]
tm_bndrs
, rd_lhs :: forall pass. RuleDecl pass -> Located (HsExpr pass)
rd_lhs = Located (HsExpr GhcRn)
lhs
, rd_rhs :: forall pass. RuleDecl pass -> Located (HsExpr pass)
rd_rhs = Located (HsExpr GhcRn)
rhs })
= MsgDoc -> TcM (RuleDecl GhcTc) -> TcM (RuleDecl GhcTc)
forall a. MsgDoc -> TcM a -> TcM a
addErrCtxt (RuleName -> MsgDoc
ruleCtxt RuleName
name) (TcM (RuleDecl GhcTc) -> TcM (RuleDecl GhcTc))
-> TcM (RuleDecl GhcTc) -> TcM (RuleDecl GhcTc)
forall a b. (a -> b) -> a -> b
$
do { String -> MsgDoc -> TcRn ()
traceTc String
"---- Rule ------" (Located (SourceText, RuleName) -> MsgDoc
pprFullRuleName Located (SourceText, RuleName)
rname)
; (TcLevel
tc_lvl, ([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
stuff) <- TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
-> TcM
(TcLevel,
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType))
forall a. TcM a -> TcM (TcLevel, a)
pushTcLevelM (TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
-> TcM
(TcLevel,
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)))
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
-> TcM
(TcLevel,
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType))
forall a b. (a -> b) -> a -> b
$
Maybe [LHsTyVarBndr () GhcRn]
-> [LRuleBndr GhcRn]
-> Located (HsExpr GhcRn)
-> Located (HsExpr GhcRn)
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
generateRuleConstraints Maybe [LHsTyVarBndr () GhcRn]
Maybe [LHsTyVarBndr () (NoGhcTc GhcRn)]
ty_bndrs [LRuleBndr GhcRn]
tm_bndrs Located (HsExpr GhcRn)
lhs Located (HsExpr GhcRn)
rhs
; let ([TcTyVar]
id_bndrs, LHsExpr GhcTc
lhs', WantedConstraints
lhs_wanted
, LHsExpr GhcTc
rhs', WantedConstraints
rhs_wanted, TcType
rule_ty) = ([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
stuff
; String -> MsgDoc -> TcRn ()
traceTc String
"tcRule 1" ([MsgDoc] -> MsgDoc
vcat [ Located (SourceText, RuleName) -> MsgDoc
pprFullRuleName Located (SourceText, RuleName)
rname
, WantedConstraints -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr WantedConstraints
lhs_wanted
, WantedConstraints -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr WantedConstraints
rhs_wanted ])
; ([TcTyVar]
lhs_evs, WantedConstraints
residual_lhs_wanted)
<- RuleName
-> TcLevel
-> WantedConstraints
-> WantedConstraints
-> TcM ([TcTyVar], WantedConstraints)
simplifyRule RuleName
name TcLevel
tc_lvl WantedConstraints
lhs_wanted WantedConstraints
rhs_wanted
; let tpl_ids :: [TcTyVar]
tpl_ids = [TcTyVar]
lhs_evs [TcTyVar] -> [TcTyVar] -> [TcTyVar]
forall a. [a] -> [a] -> [a]
++ [TcTyVar]
id_bndrs
; CandidatesQTvs
forall_tkvs <- [TcType] -> TcM CandidatesQTvs
candidateQTyVarsOfTypes (TcType
rule_ty TcType -> [TcType] -> [TcType]
forall a. a -> [a] -> [a]
: (TcTyVar -> TcType) -> [TcTyVar] -> [TcType]
forall a b. (a -> b) -> [a] -> [b]
map TcTyVar -> TcType
idType [TcTyVar]
tpl_ids)
; [TcTyVar]
qtkvs <- CandidatesQTvs -> TcM [TcTyVar]
quantifyTyVars CandidatesQTvs
forall_tkvs
; String -> MsgDoc -> TcRn ()
traceTc String
"tcRule" ([MsgDoc] -> MsgDoc
vcat [ Located (SourceText, RuleName) -> MsgDoc
pprFullRuleName Located (SourceText, RuleName)
rname
, CandidatesQTvs -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr CandidatesQTvs
forall_tkvs
, [TcTyVar] -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr [TcTyVar]
qtkvs
, TcType -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr TcType
rule_ty
, [MsgDoc] -> MsgDoc
vcat [ TcTyVar -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr TcTyVar
id MsgDoc -> MsgDoc -> MsgDoc
<+> MsgDoc
dcolon MsgDoc -> MsgDoc -> MsgDoc
<+> TcType -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr (TcTyVar -> TcType
idType TcTyVar
id) | TcTyVar
id <- [TcTyVar]
tpl_ids ]
])
; let skol_info :: SkolemInfo
skol_info = RuleName -> SkolemInfo
RuleSkol RuleName
name
; (Bag Implication
lhs_implic, TcEvBinds
lhs_binds) <- TcLevel
-> SkolemInfo
-> [TcTyVar]
-> [TcTyVar]
-> WantedConstraints
-> TcM (Bag Implication, TcEvBinds)
buildImplicationFor TcLevel
tc_lvl SkolemInfo
skol_info [TcTyVar]
qtkvs
[TcTyVar]
lhs_evs WantedConstraints
residual_lhs_wanted
; (Bag Implication
rhs_implic, TcEvBinds
rhs_binds) <- TcLevel
-> SkolemInfo
-> [TcTyVar]
-> [TcTyVar]
-> WantedConstraints
-> TcM (Bag Implication, TcEvBinds)
buildImplicationFor TcLevel
tc_lvl SkolemInfo
skol_info [TcTyVar]
qtkvs
[TcTyVar]
lhs_evs WantedConstraints
rhs_wanted
; Bag Implication -> TcRn ()
emitImplications (Bag Implication
lhs_implic Bag Implication -> Bag Implication -> Bag Implication
forall a. Bag a -> Bag a -> Bag a
`unionBags` Bag Implication
rhs_implic)
; RuleDecl GhcTc -> TcM (RuleDecl GhcTc)
forall (m :: * -> *) a. Monad m => a -> m a
return (RuleDecl GhcTc -> TcM (RuleDecl GhcTc))
-> RuleDecl GhcTc -> TcM (RuleDecl GhcTc)
forall a b. (a -> b) -> a -> b
$ HsRule :: forall pass.
XHsRule pass
-> Located (SourceText, RuleName)
-> Activation
-> Maybe [LHsTyVarBndr () (NoGhcTc pass)]
-> [LRuleBndr pass]
-> Located (HsExpr pass)
-> Located (HsExpr pass)
-> RuleDecl pass
HsRule { rd_ext :: XHsRule GhcTc
rd_ext = XHsRule GhcRn
XHsRule GhcTc
ext
, rd_name :: Located (SourceText, RuleName)
rd_name = Located (SourceText, RuleName)
rname
, rd_act :: Activation
rd_act = Activation
act
, rd_tyvs :: Maybe [LHsTyVarBndr () (NoGhcTc GhcTc)]
rd_tyvs = Maybe [LHsTyVarBndr () (NoGhcTc GhcRn)]
Maybe [LHsTyVarBndr () (NoGhcTc GhcTc)]
ty_bndrs
, rd_tmvs :: [LRuleBndr GhcTc]
rd_tmvs = (TcTyVar -> LRuleBndr GhcTc) -> [TcTyVar] -> [LRuleBndr GhcTc]
forall a b. (a -> b) -> [a] -> [b]
map (RuleBndr GhcTc -> LRuleBndr GhcTc
forall e. e -> Located e
noLoc (RuleBndr GhcTc -> LRuleBndr GhcTc)
-> (TcTyVar -> RuleBndr GhcTc) -> TcTyVar -> LRuleBndr GhcTc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XCRuleBndr GhcTc -> Located (IdP GhcTc) -> RuleBndr GhcTc
forall pass. XCRuleBndr pass -> Located (IdP pass) -> RuleBndr pass
RuleBndr NoExtField
XCRuleBndr GhcTc
noExtField (GenLocated SrcSpan TcTyVar -> RuleBndr GhcTc)
-> (TcTyVar -> GenLocated SrcSpan TcTyVar)
-> TcTyVar
-> RuleBndr GhcTc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TcTyVar -> GenLocated SrcSpan TcTyVar
forall e. e -> Located e
noLoc)
([TcTyVar]
qtkvs [TcTyVar] -> [TcTyVar] -> [TcTyVar]
forall a. [a] -> [a] -> [a]
++ [TcTyVar]
tpl_ids)
, rd_lhs :: LHsExpr GhcTc
rd_lhs = TcEvBinds -> LHsExpr GhcTc -> LHsExpr GhcTc
mkHsDictLet TcEvBinds
lhs_binds LHsExpr GhcTc
lhs'
, rd_rhs :: LHsExpr GhcTc
rd_rhs = TcEvBinds -> LHsExpr GhcTc -> LHsExpr GhcTc
mkHsDictLet TcEvBinds
rhs_binds LHsExpr GhcTc
rhs' } }
generateRuleConstraints :: Maybe [LHsTyVarBndr () GhcRn] -> [LRuleBndr GhcRn]
-> LHsExpr GhcRn -> LHsExpr GhcRn
-> TcM ( [TcId]
, LHsExpr GhcTc, WantedConstraints
, LHsExpr GhcTc, WantedConstraints
, TcType )
generateRuleConstraints :: Maybe [LHsTyVarBndr () GhcRn]
-> [LRuleBndr GhcRn]
-> Located (HsExpr GhcRn)
-> Located (HsExpr GhcRn)
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
generateRuleConstraints Maybe [LHsTyVarBndr () GhcRn]
ty_bndrs [LRuleBndr GhcRn]
tm_bndrs Located (HsExpr GhcRn)
lhs Located (HsExpr GhcRn)
rhs
= do { (([TcTyVar]
tv_bndrs, [TcTyVar]
id_bndrs), WantedConstraints
bndr_wanted) <- TcM ([TcTyVar], [TcTyVar])
-> TcM (([TcTyVar], [TcTyVar]), WantedConstraints)
forall a. TcM a -> TcM (a, WantedConstraints)
captureConstraints (TcM ([TcTyVar], [TcTyVar])
-> TcM (([TcTyVar], [TcTyVar]), WantedConstraints))
-> TcM ([TcTyVar], [TcTyVar])
-> TcM (([TcTyVar], [TcTyVar]), WantedConstraints)
forall a b. (a -> b) -> a -> b
$
Maybe [LHsTyVarBndr () GhcRn]
-> [LRuleBndr GhcRn] -> TcM ([TcTyVar], [TcTyVar])
tcRuleBndrs Maybe [LHsTyVarBndr () GhcRn]
ty_bndrs [LRuleBndr GhcRn]
tm_bndrs
; [TcTyVar]
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
forall r. [TcTyVar] -> TcM r -> TcM r
tcExtendTyVarEnv [TcTyVar]
tv_bndrs (TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType))
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
forall a b. (a -> b) -> a -> b
$
[TcTyVar]
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
forall r. [TcTyVar] -> TcM r -> TcM r
tcExtendIdEnv [TcTyVar]
id_bndrs (TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType))
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
forall a b. (a -> b) -> a -> b
$
do {
((LHsExpr GhcTc
lhs', TcType
rule_ty), WantedConstraints
lhs_wanted) <- TcM (LHsExpr GhcTc, TcType)
-> TcM ((LHsExpr GhcTc, TcType), WantedConstraints)
forall a. TcM a -> TcM (a, WantedConstraints)
captureConstraints (Located (HsExpr GhcRn) -> TcM (LHsExpr GhcTc, TcType)
tcInferRho Located (HsExpr GhcRn)
lhs)
; (LHsExpr GhcTc
rhs', WantedConstraints
rhs_wanted) <- TcM (LHsExpr GhcTc) -> TcM (LHsExpr GhcTc, WantedConstraints)
forall a. TcM a -> TcM (a, WantedConstraints)
captureConstraints (TcM (LHsExpr GhcTc) -> TcM (LHsExpr GhcTc, WantedConstraints))
-> TcM (LHsExpr GhcTc) -> TcM (LHsExpr GhcTc, WantedConstraints)
forall a b. (a -> b) -> a -> b
$
Located (HsExpr GhcRn) -> TcType -> TcM (LHsExpr GhcTc)
tcCheckMonoExpr Located (HsExpr GhcRn)
rhs TcType
rule_ty
; let all_lhs_wanted :: WantedConstraints
all_lhs_wanted = WantedConstraints
bndr_wanted WantedConstraints -> WantedConstraints -> WantedConstraints
`andWC` WantedConstraints
lhs_wanted
; ([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
-> TcM
([TcTyVar], LHsExpr GhcTc, WantedConstraints, LHsExpr GhcTc,
WantedConstraints, TcType)
forall (m :: * -> *) a. Monad m => a -> m a
return ([TcTyVar]
id_bndrs, LHsExpr GhcTc
lhs', WantedConstraints
all_lhs_wanted, LHsExpr GhcTc
rhs', WantedConstraints
rhs_wanted, TcType
rule_ty) } }
tcRuleBndrs :: Maybe [LHsTyVarBndr () GhcRn] -> [LRuleBndr GhcRn]
-> TcM ([TcTyVar], [Id])
tcRuleBndrs :: Maybe [LHsTyVarBndr () GhcRn]
-> [LRuleBndr GhcRn] -> TcM ([TcTyVar], [TcTyVar])
tcRuleBndrs (Just [LHsTyVarBndr () GhcRn]
bndrs) [LRuleBndr GhcRn]
xs
= do { ([VarBndr TcTyVar ()]
tybndrs1,([TcTyVar]
tys2,[TcTyVar]
tms)) <- [LHsTyVarBndr () GhcRn]
-> TcM ([TcTyVar], [TcTyVar])
-> TcM ([VarBndr TcTyVar ()], ([TcTyVar], [TcTyVar]))
forall flag a.
OutputableBndrFlag flag =>
[LHsTyVarBndr flag GhcRn]
-> TcM a -> TcM ([VarBndr TcTyVar flag], a)
bindExplicitTKBndrs_Skol [LHsTyVarBndr () GhcRn]
bndrs (TcM ([TcTyVar], [TcTyVar])
-> TcM ([VarBndr TcTyVar ()], ([TcTyVar], [TcTyVar])))
-> TcM ([TcTyVar], [TcTyVar])
-> TcM ([VarBndr TcTyVar ()], ([TcTyVar], [TcTyVar]))
forall a b. (a -> b) -> a -> b
$
[LRuleBndr GhcRn] -> TcM ([TcTyVar], [TcTyVar])
tcRuleTmBndrs [LRuleBndr GhcRn]
xs
; let tys1 :: [TcTyVar]
tys1 = [VarBndr TcTyVar ()] -> [TcTyVar]
forall tv argf. [VarBndr tv argf] -> [tv]
binderVars [VarBndr TcTyVar ()]
tybndrs1
; ([TcTyVar], [TcTyVar]) -> TcM ([TcTyVar], [TcTyVar])
forall (m :: * -> *) a. Monad m => a -> m a
return ([TcTyVar]
tys1 [TcTyVar] -> [TcTyVar] -> [TcTyVar]
forall a. [a] -> [a] -> [a]
++ [TcTyVar]
tys2, [TcTyVar]
tms) }
tcRuleBndrs Maybe [LHsTyVarBndr () GhcRn]
Nothing [LRuleBndr GhcRn]
xs
= [LRuleBndr GhcRn] -> TcM ([TcTyVar], [TcTyVar])
tcRuleTmBndrs [LRuleBndr GhcRn]
xs
tcRuleTmBndrs :: [LRuleBndr GhcRn] -> TcM ([TcTyVar],[Id])
tcRuleTmBndrs :: [LRuleBndr GhcRn] -> TcM ([TcTyVar], [TcTyVar])
tcRuleTmBndrs [] = ([TcTyVar], [TcTyVar]) -> TcM ([TcTyVar], [TcTyVar])
forall (m :: * -> *) a. Monad m => a -> m a
return ([],[])
tcRuleTmBndrs (L SrcSpan
_ (RuleBndr XCRuleBndr GhcRn
_ (L SrcSpan
_ IdP GhcRn
name)) : [LRuleBndr GhcRn]
rule_bndrs)
= do { TcType
ty <- TcM TcType
newOpenFlexiTyVarTy
; ([TcTyVar]
tyvars, [TcTyVar]
tmvars) <- [LRuleBndr GhcRn] -> TcM ([TcTyVar], [TcTyVar])
tcRuleTmBndrs [LRuleBndr GhcRn]
rule_bndrs
; ([TcTyVar], [TcTyVar]) -> TcM ([TcTyVar], [TcTyVar])
forall (m :: * -> *) a. Monad m => a -> m a
return ([TcTyVar]
tyvars, HasDebugCallStack => Name -> TcType -> TcType -> TcTyVar
Name -> TcType -> TcType -> TcTyVar
mkLocalId Name
IdP GhcRn
name TcType
Many TcType
ty TcTyVar -> [TcTyVar] -> [TcTyVar]
forall a. a -> [a] -> [a]
: [TcTyVar]
tmvars) }
tcRuleTmBndrs (L SrcSpan
_ (RuleBndrSig XRuleBndrSig GhcRn
_ (L SrcSpan
_ IdP GhcRn
name) HsPatSigType GhcRn
rn_ty) : [LRuleBndr GhcRn]
rule_bndrs)
= do { let ctxt :: UserTypeCtxt
ctxt = Name -> UserTypeCtxt
RuleSigCtxt Name
IdP GhcRn
name
; ([(Name, TcTyVar)]
_ , [(Name, TcTyVar)]
tvs, TcType
id_ty) <- UserTypeCtxt
-> HsPatSigType GhcRn
-> TcM ([(Name, TcTyVar)], [(Name, TcTyVar)], TcType)
tcHsPatSigType UserTypeCtxt
ctxt HsPatSigType GhcRn
rn_ty
; let id :: TcTyVar
id = HasDebugCallStack => Name -> TcType -> TcType -> TcTyVar
Name -> TcType -> TcType -> TcTyVar
mkLocalId Name
IdP GhcRn
name TcType
Many TcType
id_ty
; ([TcTyVar]
tyvars, [TcTyVar]
tmvars) <- [(Name, TcTyVar)]
-> TcM ([TcTyVar], [TcTyVar]) -> TcM ([TcTyVar], [TcTyVar])
forall r. [(Name, TcTyVar)] -> TcM r -> TcM r
tcExtendNameTyVarEnv [(Name, TcTyVar)]
tvs (TcM ([TcTyVar], [TcTyVar]) -> TcM ([TcTyVar], [TcTyVar]))
-> TcM ([TcTyVar], [TcTyVar]) -> TcM ([TcTyVar], [TcTyVar])
forall a b. (a -> b) -> a -> b
$
[LRuleBndr GhcRn] -> TcM ([TcTyVar], [TcTyVar])
tcRuleTmBndrs [LRuleBndr GhcRn]
rule_bndrs
; ([TcTyVar], [TcTyVar]) -> TcM ([TcTyVar], [TcTyVar])
forall (m :: * -> *) a. Monad m => a -> m a
return (((Name, TcTyVar) -> TcTyVar) -> [(Name, TcTyVar)] -> [TcTyVar]
forall a b. (a -> b) -> [a] -> [b]
map (Name, TcTyVar) -> TcTyVar
forall a b. (a, b) -> b
snd [(Name, TcTyVar)]
tvs [TcTyVar] -> [TcTyVar] -> [TcTyVar]
forall a. [a] -> [a] -> [a]
++ [TcTyVar]
tyvars, TcTyVar
id TcTyVar -> [TcTyVar] -> [TcTyVar]
forall a. a -> [a] -> [a]
: [TcTyVar]
tmvars) }
ruleCtxt :: FastString -> SDoc
ruleCtxt :: RuleName -> MsgDoc
ruleCtxt RuleName
name = String -> MsgDoc
text String
"When checking the rewrite rule" MsgDoc -> MsgDoc -> MsgDoc
<+>
MsgDoc -> MsgDoc
doubleQuotes (RuleName -> MsgDoc
ftext RuleName
name)
simplifyRule :: RuleName
-> TcLevel
-> WantedConstraints
-> WantedConstraints
-> TcM ( [EvVar]
, WantedConstraints)
simplifyRule :: RuleName
-> TcLevel
-> WantedConstraints
-> WantedConstraints
-> TcM ([TcTyVar], WantedConstraints)
simplifyRule RuleName
name TcLevel
tc_lvl WantedConstraints
lhs_wanted WantedConstraints
rhs_wanted
= do {
; WantedConstraints
lhs_clone <- WantedConstraints -> TcM WantedConstraints
cloneWC WantedConstraints
lhs_wanted
; WantedConstraints
rhs_clone <- WantedConstraints -> TcM WantedConstraints
cloneWC WantedConstraints
rhs_wanted
; TcLevel -> TcRn () -> TcRn ()
forall a. TcLevel -> TcM a -> TcM a
setTcLevel TcLevel
tc_lvl (TcRn () -> TcRn ()) -> TcRn () -> TcRn ()
forall a b. (a -> b) -> a -> b
$
TcS () -> TcRn ()
forall a. TcS a -> TcM a
runTcSDeriveds (TcS () -> TcRn ()) -> TcS () -> TcRn ()
forall a b. (a -> b) -> a -> b
$
do { WantedConstraints
_ <- WantedConstraints -> TcS WantedConstraints
solveWanteds WantedConstraints
lhs_clone
; WantedConstraints
_ <- WantedConstraints -> TcS WantedConstraints
solveWanteds WantedConstraints
rhs_clone
; () -> TcS ()
forall (m :: * -> *) a. Monad m => a -> m a
return () }
; WantedConstraints
lhs_wanted <- WantedConstraints -> TcM WantedConstraints
zonkWC WantedConstraints
lhs_wanted
; let (Cts
quant_cts, WantedConstraints
residual_lhs_wanted) = WantedConstraints -> (Cts, WantedConstraints)
getRuleQuantCts WantedConstraints
lhs_wanted
; [TcTyVar]
quant_evs <- (Ct -> IOEnv (Env TcGblEnv TcLclEnv) TcTyVar)
-> [Ct] -> TcM [TcTyVar]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Ct -> IOEnv (Env TcGblEnv TcLclEnv) TcTyVar
mk_quant_ev (Cts -> [Ct]
forall a. Bag a -> [a]
bagToList Cts
quant_cts)
; String -> MsgDoc -> TcRn ()
traceTc String
"simplifyRule" (MsgDoc -> TcRn ()) -> MsgDoc -> TcRn ()
forall a b. (a -> b) -> a -> b
$
[MsgDoc] -> MsgDoc
vcat [ String -> MsgDoc
text String
"LHS of rule" MsgDoc -> MsgDoc -> MsgDoc
<+> MsgDoc -> MsgDoc
doubleQuotes (RuleName -> MsgDoc
ftext RuleName
name)
, String -> MsgDoc
text String
"lhs_wanted" MsgDoc -> MsgDoc -> MsgDoc
<+> WantedConstraints -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr WantedConstraints
lhs_wanted
, String -> MsgDoc
text String
"rhs_wanted" MsgDoc -> MsgDoc -> MsgDoc
<+> WantedConstraints -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr WantedConstraints
rhs_wanted
, String -> MsgDoc
text String
"quant_cts" MsgDoc -> MsgDoc -> MsgDoc
<+> Cts -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr Cts
quant_cts
, String -> MsgDoc
text String
"residual_lhs_wanted" MsgDoc -> MsgDoc -> MsgDoc
<+> WantedConstraints -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr WantedConstraints
residual_lhs_wanted
]
; ([TcTyVar], WantedConstraints)
-> TcM ([TcTyVar], WantedConstraints)
forall (m :: * -> *) a. Monad m => a -> m a
return ([TcTyVar]
quant_evs, WantedConstraints
residual_lhs_wanted) }
where
mk_quant_ev :: Ct -> TcM EvVar
mk_quant_ev :: Ct -> IOEnv (Env TcGblEnv TcLclEnv) TcTyVar
mk_quant_ev Ct
ct
| CtWanted { ctev_dest :: CtEvidence -> TcEvDest
ctev_dest = TcEvDest
dest, ctev_pred :: CtEvidence -> TcType
ctev_pred = TcType
pred } <- Ct -> CtEvidence
ctEvidence Ct
ct
= case TcEvDest
dest of
EvVarDest TcTyVar
ev_id -> TcTyVar -> IOEnv (Env TcGblEnv TcLclEnv) TcTyVar
forall (m :: * -> *) a. Monad m => a -> m a
return TcTyVar
ev_id
HoleDest CoercionHole
hole ->
do { TcTyVar
ev_id <- TcType -> IOEnv (Env TcGblEnv TcLclEnv) TcTyVar
forall gbl lcl. TcType -> TcRnIf gbl lcl TcTyVar
newEvVar TcType
pred
; CoercionHole -> Coercion -> TcRn ()
fillCoercionHole CoercionHole
hole (TcTyVar -> Coercion
mkTcCoVarCo TcTyVar
ev_id)
; TcTyVar -> IOEnv (Env TcGblEnv TcLclEnv) TcTyVar
forall (m :: * -> *) a. Monad m => a -> m a
return TcTyVar
ev_id }
mk_quant_ev Ct
ct = String -> MsgDoc -> IOEnv (Env TcGblEnv TcLclEnv) TcTyVar
forall a. HasCallStack => String -> MsgDoc -> a
pprPanic String
"mk_quant_ev" (Ct -> MsgDoc
forall a. Outputable a => a -> MsgDoc
ppr Ct
ct)
getRuleQuantCts :: WantedConstraints -> (Cts, WantedConstraints)
getRuleQuantCts :: WantedConstraints -> (Cts, WantedConstraints)
getRuleQuantCts WantedConstraints
wc
= TcTyCoVarSet -> WantedConstraints -> (Cts, WantedConstraints)
float_wc TcTyCoVarSet
emptyVarSet WantedConstraints
wc
where
float_wc :: TcTyCoVarSet -> WantedConstraints -> (Cts, WantedConstraints)
float_wc :: TcTyCoVarSet -> WantedConstraints -> (Cts, WantedConstraints)
float_wc TcTyCoVarSet
skol_tvs (WC { wc_simple :: WantedConstraints -> Cts
wc_simple = Cts
simples, wc_impl :: WantedConstraints -> Bag Implication
wc_impl = Bag Implication
implics, wc_holes :: WantedConstraints -> Bag Hole
wc_holes = Bag Hole
holes })
= ( Cts
simple_yes Cts -> Cts -> Cts
`andCts` Cts
implic_yes
, WantedConstraints
emptyWC { wc_simple :: Cts
wc_simple = Cts
simple_no, wc_impl :: Bag Implication
wc_impl = Bag Implication
implics_no, wc_holes :: Bag Hole
wc_holes = Bag Hole
holes })
where
(Cts
simple_yes, Cts
simple_no) = (Ct -> Bool) -> Cts -> (Cts, Cts)
forall a. (a -> Bool) -> Bag a -> (Bag a, Bag a)
partitionBag (TcTyCoVarSet -> Ct -> Bool
rule_quant_ct TcTyCoVarSet
skol_tvs) Cts
simples
(Cts
implic_yes, Bag Implication
implics_no) = (Cts -> Implication -> (Cts, Implication))
-> Cts -> Bag Implication -> (Cts, Bag Implication)
forall acc x y.
(acc -> x -> (acc, y)) -> acc -> Bag x -> (acc, Bag y)
mapAccumBagL (TcTyCoVarSet -> Cts -> Implication -> (Cts, Implication)
float_implic TcTyCoVarSet
skol_tvs)
Cts
forall a. Bag a
emptyBag Bag Implication
implics
float_implic :: TcTyCoVarSet -> Cts -> Implication -> (Cts, Implication)
float_implic :: TcTyCoVarSet -> Cts -> Implication -> (Cts, Implication)
float_implic TcTyCoVarSet
skol_tvs Cts
yes1 Implication
imp
= (Cts
yes1 Cts -> Cts -> Cts
`andCts` Cts
yes2, Implication
imp { ic_wanted :: WantedConstraints
ic_wanted = WantedConstraints
no })
where
(Cts
yes2, WantedConstraints
no) = TcTyCoVarSet -> WantedConstraints -> (Cts, WantedConstraints)
float_wc TcTyCoVarSet
new_skol_tvs (Implication -> WantedConstraints
ic_wanted Implication
imp)
new_skol_tvs :: TcTyCoVarSet
new_skol_tvs = TcTyCoVarSet
skol_tvs TcTyCoVarSet -> [TcTyVar] -> TcTyCoVarSet
`extendVarSetList` Implication -> [TcTyVar]
ic_skols Implication
imp
rule_quant_ct :: TcTyCoVarSet -> Ct -> Bool
rule_quant_ct :: TcTyCoVarSet -> Ct -> Bool
rule_quant_ct TcTyCoVarSet
skol_tvs Ct
ct
| EqPred EqRel
_ TcType
t1 TcType
t2 <- TcType -> Pred
classifyPredType (Ct -> TcType
ctPred Ct
ct)
, Bool -> Bool
not (TcType -> TcType -> Bool
ok_eq TcType
t1 TcType
t2)
= Bool
False
| Bool
otherwise
= Ct -> TcTyCoVarSet
tyCoVarsOfCt Ct
ct TcTyCoVarSet -> TcTyCoVarSet -> Bool
`disjointVarSet` TcTyCoVarSet
skol_tvs
ok_eq :: TcType -> TcType -> Bool
ok_eq TcType
t1 TcType
t2
| TcType
t1 HasDebugCallStack => TcType -> TcType -> Bool
TcType -> TcType -> Bool
`tcEqType` TcType
t2 = Bool
False
| Bool
otherwise = TcType -> Bool
is_fun_app TcType
t1 Bool -> Bool -> Bool
|| TcType -> Bool
is_fun_app TcType
t2
is_fun_app :: TcType -> Bool
is_fun_app TcType
ty
= case TcType -> Maybe TyCon
tyConAppTyCon_maybe TcType
ty of
Just TyCon
tc -> TyCon -> Bool
isTypeFamilyTyCon TyCon
tc
Maybe TyCon
Nothing -> Bool
False