{-# LANGUAGE CPP, DeriveDataTypeable #-}
module TcEvidence (
HsWrapper(..),
(<.>), mkWpTyApps, mkWpEvApps, mkWpEvVarApps, mkWpTyLams,
mkWpLams, mkWpLet, mkWpCastN, mkWpCastR, collectHsWrapBinders,
mkWpFun, idHsWrapper, isIdHsWrapper, isErasableHsWrapper,
pprHsWrapper,
TcEvBinds(..), EvBindsVar(..),
EvBindMap(..), emptyEvBindMap, extendEvBinds,
lookupEvBind, evBindMapBinds, foldEvBindMap, filterEvBindMap,
isEmptyEvBindMap,
EvBind(..), emptyTcEvBinds, isEmptyTcEvBinds, mkGivenEvBind, mkWantedEvBind,
evBindVar, isCoEvBindsVar,
EvTerm(..), EvExpr,
evId, evCoercion, evCast, evDFunApp, evDataConApp, evSelector,
mkEvCast, evVarsOfTerm, mkEvScSelectors, evTypeable, findNeededEvVars,
evTermCoercion, evTermCoercion_maybe,
EvCallStack(..),
EvTypeable(..),
TcCoercion, TcCoercionR, TcCoercionN, TcCoercionP, CoercionHole,
TcMCoercion,
Role(..), LeftOrRight(..), pickLR,
mkTcReflCo, mkTcNomReflCo, mkTcRepReflCo,
mkTcTyConAppCo, mkTcAppCo, mkTcFunCo,
mkTcAxInstCo, mkTcUnbranchedAxInstCo, mkTcForAllCo, mkTcForAllCos,
mkTcSymCo, mkTcTransCo, mkTcNthCo, mkTcLRCo, mkTcSubCo, maybeTcSubCo,
tcDowngradeRole,
mkTcAxiomRuleCo, mkTcGReflRightCo, mkTcGReflLeftCo, mkTcPhantomCo,
mkTcCoherenceLeftCo,
mkTcCoherenceRightCo,
mkTcKindCo,
tcCoercionKind, coVarsOfTcCo,
mkTcCoVarCo,
isTcReflCo, isTcReflexiveCo, isTcGReflMCo, tcCoToMCo,
tcCoercionRole,
unwrapIP, wrapIP
) where
#include "HsVersions.h"
import GhcPrelude
import Var
import CoAxiom
import Coercion
import PprCore ()
import TcType
import Type
import TyCon
import DataCon( DataCon, dataConWrapId )
import Class( Class )
import PrelNames
import DynFlags ( gopt, GeneralFlag(Opt_PrintTypecheckerElaboration) )
import VarEnv
import VarSet
import Predicate
import Name
import Pair
import CoreSyn
import Class ( classSCSelId )
import CoreFVs ( exprSomeFreeVars )
import Util
import Bag
import qualified Data.Data as Data
import Outputable
import SrcLoc
import Data.IORef( IORef )
import UniqSet
type TcCoercion = Coercion
type TcCoercionN = CoercionN
type TcCoercionR = CoercionR
type TcCoercionP = CoercionP
type TcMCoercion = MCoercion
mkTcReflCo :: Role -> TcType -> TcCoercion
mkTcSymCo :: TcCoercion -> TcCoercion
mkTcTransCo :: TcCoercion -> TcCoercion -> TcCoercion
mkTcNomReflCo :: TcType -> TcCoercionN
mkTcRepReflCo :: TcType -> TcCoercionR
mkTcTyConAppCo :: Role -> TyCon -> [TcCoercion] -> TcCoercion
mkTcAppCo :: TcCoercion -> TcCoercionN -> TcCoercion
mkTcFunCo :: Role -> TcCoercion -> TcCoercion -> TcCoercion
mkTcAxInstCo :: Role -> CoAxiom br -> BranchIndex
-> [TcType] -> [TcCoercion] -> TcCoercion
mkTcUnbranchedAxInstCo :: CoAxiom Unbranched -> [TcType]
-> [TcCoercion] -> TcCoercionR
mkTcForAllCo :: TyVar -> TcCoercionN -> TcCoercion -> TcCoercion
mkTcForAllCos :: [(TyVar, TcCoercionN)] -> TcCoercion -> TcCoercion
mkTcNthCo :: Role -> Int -> TcCoercion -> TcCoercion
mkTcLRCo :: LeftOrRight -> TcCoercion -> TcCoercion
mkTcSubCo :: TcCoercionN -> TcCoercionR
tcDowngradeRole :: Role -> Role -> TcCoercion -> TcCoercion
mkTcAxiomRuleCo :: CoAxiomRule -> [TcCoercion] -> TcCoercionR
mkTcGReflRightCo :: Role -> TcType -> TcCoercionN -> TcCoercion
mkTcGReflLeftCo :: Role -> TcType -> TcCoercionN -> TcCoercion
mkTcCoherenceLeftCo :: Role -> TcType -> TcCoercionN
-> TcCoercion -> TcCoercion
mkTcCoherenceRightCo :: Role -> TcType -> TcCoercionN
-> TcCoercion -> TcCoercion
mkTcPhantomCo :: TcCoercionN -> TcType -> TcType -> TcCoercionP
mkTcKindCo :: TcCoercion -> TcCoercionN
mkTcCoVarCo :: CoVar -> TcCoercion
tcCoercionKind :: TcCoercion -> Pair TcType
tcCoercionRole :: TcCoercion -> Role
coVarsOfTcCo :: TcCoercion -> TcTyCoVarSet
isTcReflCo :: TcCoercion -> Bool
isTcGReflMCo :: TcMCoercion -> Bool
isTcReflexiveCo :: TcCoercion -> Bool
mkTcReflCo :: Role -> TcType -> TcCoercion
mkTcReflCo = Role -> TcType -> TcCoercion
mkReflCo
mkTcSymCo :: TcCoercion -> TcCoercion
mkTcSymCo = TcCoercion -> TcCoercion
mkSymCo
mkTcTransCo :: TcCoercion -> TcCoercion -> TcCoercion
mkTcTransCo = TcCoercion -> TcCoercion -> TcCoercion
mkTransCo
mkTcNomReflCo :: TcType -> TcCoercion
mkTcNomReflCo = TcType -> TcCoercion
mkNomReflCo
mkTcRepReflCo :: TcType -> TcCoercion
mkTcRepReflCo = TcType -> TcCoercion
mkRepReflCo
mkTcTyConAppCo :: Role -> TyCon -> [TcCoercion] -> TcCoercion
mkTcTyConAppCo = HasDebugCallStack => Role -> TyCon -> [TcCoercion] -> TcCoercion
Role -> TyCon -> [TcCoercion] -> TcCoercion
mkTyConAppCo
mkTcAppCo :: TcCoercion -> TcCoercion -> TcCoercion
mkTcAppCo = TcCoercion -> TcCoercion -> TcCoercion
mkAppCo
mkTcFunCo :: Role -> TcCoercion -> TcCoercion -> TcCoercion
mkTcFunCo = Role -> TcCoercion -> TcCoercion -> TcCoercion
mkFunCo
mkTcAxInstCo :: Role
-> CoAxiom br
-> BranchIndex
-> [TcType]
-> [TcCoercion]
-> TcCoercion
mkTcAxInstCo = Role
-> CoAxiom br
-> BranchIndex
-> [TcType]
-> [TcCoercion]
-> TcCoercion
forall (br :: BranchFlag).
Role
-> CoAxiom br
-> BranchIndex
-> [TcType]
-> [TcCoercion]
-> TcCoercion
mkAxInstCo
mkTcUnbranchedAxInstCo :: CoAxiom Unbranched -> [TcType] -> [TcCoercion] -> TcCoercion
mkTcUnbranchedAxInstCo = Role
-> CoAxiom Unbranched -> [TcType] -> [TcCoercion] -> TcCoercion
mkUnbranchedAxInstCo Role
Representational
mkTcForAllCo :: TyVar -> TcCoercion -> TcCoercion -> TcCoercion
mkTcForAllCo = TyVar -> TcCoercion -> TcCoercion -> TcCoercion
mkForAllCo
mkTcForAllCos :: [(TyVar, TcCoercion)] -> TcCoercion -> TcCoercion
mkTcForAllCos = [(TyVar, TcCoercion)] -> TcCoercion -> TcCoercion
mkForAllCos
mkTcNthCo :: Role -> BranchIndex -> TcCoercion -> TcCoercion
mkTcNthCo = HasDebugCallStack =>
Role -> BranchIndex -> TcCoercion -> TcCoercion
Role -> BranchIndex -> TcCoercion -> TcCoercion
mkNthCo
mkTcLRCo :: LeftOrRight -> TcCoercion -> TcCoercion
mkTcLRCo = LeftOrRight -> TcCoercion -> TcCoercion
mkLRCo
mkTcSubCo :: TcCoercion -> TcCoercion
mkTcSubCo = TcCoercion -> TcCoercion
mkSubCo
tcDowngradeRole :: Role -> Role -> TcCoercion -> TcCoercion
tcDowngradeRole = Role -> Role -> TcCoercion -> TcCoercion
downgradeRole
mkTcAxiomRuleCo :: CoAxiomRule -> [TcCoercion] -> TcCoercion
mkTcAxiomRuleCo = CoAxiomRule -> [TcCoercion] -> TcCoercion
mkAxiomRuleCo
mkTcGReflRightCo :: Role -> TcType -> TcCoercion -> TcCoercion
mkTcGReflRightCo = Role -> TcType -> TcCoercion -> TcCoercion
mkGReflRightCo
mkTcGReflLeftCo :: Role -> TcType -> TcCoercion -> TcCoercion
mkTcGReflLeftCo = Role -> TcType -> TcCoercion -> TcCoercion
mkGReflLeftCo
mkTcCoherenceLeftCo :: Role -> TcType -> TcCoercion -> TcCoercion -> TcCoercion
mkTcCoherenceLeftCo = Role -> TcType -> TcCoercion -> TcCoercion -> TcCoercion
mkCoherenceLeftCo
mkTcCoherenceRightCo :: Role -> TcType -> TcCoercion -> TcCoercion -> TcCoercion
mkTcCoherenceRightCo = Role -> TcType -> TcCoercion -> TcCoercion -> TcCoercion
mkCoherenceRightCo
mkTcPhantomCo :: TcCoercion -> TcType -> TcType -> TcCoercion
mkTcPhantomCo = TcCoercion -> TcType -> TcType -> TcCoercion
mkPhantomCo
mkTcKindCo :: TcCoercion -> TcCoercion
mkTcKindCo = TcCoercion -> TcCoercion
mkKindCo
mkTcCoVarCo :: TyVar -> TcCoercion
mkTcCoVarCo = TyVar -> TcCoercion
mkCoVarCo
tcCoercionKind :: TcCoercion -> Pair TcType
tcCoercionKind = TcCoercion -> Pair TcType
coercionKind
tcCoercionRole :: TcCoercion -> Role
tcCoercionRole = TcCoercion -> Role
coercionRole
coVarsOfTcCo :: TcCoercion -> TcTyCoVarSet
coVarsOfTcCo = TcCoercion -> TcTyCoVarSet
coVarsOfCo
isTcReflCo :: TcCoercion -> Bool
isTcReflCo = TcCoercion -> Bool
isReflCo
isTcGReflMCo :: TcMCoercion -> Bool
isTcGReflMCo = TcMCoercion -> Bool
isGReflMCo
isTcReflexiveCo :: TcCoercion -> Bool
isTcReflexiveCo = TcCoercion -> Bool
isReflexiveCo
tcCoToMCo :: TcCoercion -> TcMCoercion
tcCoToMCo :: TcCoercion -> TcMCoercion
tcCoToMCo = TcCoercion -> TcMCoercion
coToMCo
maybeTcSubCo :: EqRel -> TcCoercion -> TcCoercion
maybeTcSubCo :: EqRel -> TcCoercion -> TcCoercion
maybeTcSubCo EqRel
NomEq = TcCoercion -> TcCoercion
forall a. a -> a
id
maybeTcSubCo EqRel
ReprEq = TcCoercion -> TcCoercion
mkTcSubCo
data HsWrapper
= WpHole
| WpCompose HsWrapper HsWrapper
| WpFun HsWrapper HsWrapper TcType SDoc
| WpCast TcCoercionR
| WpEvLam EvVar
| WpEvApp EvTerm
| WpTyLam TyVar
| WpTyApp KindOrType
| WpLet TcEvBinds
instance Data.Data HsWrapper where
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsWrapper -> c HsWrapper
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
_ forall g. g -> c g
z HsWrapper
WpHole = HsWrapper -> c HsWrapper
forall g. g -> c g
z HsWrapper
WpHole
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
k forall g. g -> c g
z (WpCompose HsWrapper
a1 HsWrapper
a2) = (HsWrapper -> HsWrapper -> HsWrapper)
-> c (HsWrapper -> HsWrapper -> HsWrapper)
forall g. g -> c g
z HsWrapper -> HsWrapper -> HsWrapper
WpCompose c (HsWrapper -> HsWrapper -> HsWrapper)
-> HsWrapper -> c (HsWrapper -> HsWrapper)
forall d b. Data d => c (d -> b) -> d -> c b
`k` HsWrapper
a1 c (HsWrapper -> HsWrapper) -> HsWrapper -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
`k` HsWrapper
a2
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
k forall g. g -> c g
z (WpFun HsWrapper
a1 HsWrapper
a2 TcType
a3 SDoc
_) = (HsWrapper -> HsWrapper -> TcType -> HsWrapper)
-> c (HsWrapper -> HsWrapper -> TcType -> HsWrapper)
forall g. g -> c g
z HsWrapper -> HsWrapper -> TcType -> HsWrapper
wpFunEmpty c (HsWrapper -> HsWrapper -> TcType -> HsWrapper)
-> HsWrapper -> c (HsWrapper -> TcType -> HsWrapper)
forall d b. Data d => c (d -> b) -> d -> c b
`k` HsWrapper
a1 c (HsWrapper -> TcType -> HsWrapper)
-> HsWrapper -> c (TcType -> HsWrapper)
forall d b. Data d => c (d -> b) -> d -> c b
`k` HsWrapper
a2 c (TcType -> HsWrapper) -> TcType -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
`k` TcType
a3
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
k forall g. g -> c g
z (WpCast TcCoercion
a1) = (TcCoercion -> HsWrapper) -> c (TcCoercion -> HsWrapper)
forall g. g -> c g
z TcCoercion -> HsWrapper
WpCast c (TcCoercion -> HsWrapper) -> TcCoercion -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
`k` TcCoercion
a1
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
k forall g. g -> c g
z (WpEvLam TyVar
a1) = (TyVar -> HsWrapper) -> c (TyVar -> HsWrapper)
forall g. g -> c g
z TyVar -> HsWrapper
WpEvLam c (TyVar -> HsWrapper) -> TyVar -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
`k` TyVar
a1
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
k forall g. g -> c g
z (WpEvApp EvTerm
a1) = (EvTerm -> HsWrapper) -> c (EvTerm -> HsWrapper)
forall g. g -> c g
z EvTerm -> HsWrapper
WpEvApp c (EvTerm -> HsWrapper) -> EvTerm -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
`k` EvTerm
a1
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
k forall g. g -> c g
z (WpTyLam TyVar
a1) = (TyVar -> HsWrapper) -> c (TyVar -> HsWrapper)
forall g. g -> c g
z TyVar -> HsWrapper
WpTyLam c (TyVar -> HsWrapper) -> TyVar -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
`k` TyVar
a1
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
k forall g. g -> c g
z (WpTyApp TcType
a1) = (TcType -> HsWrapper) -> c (TcType -> HsWrapper)
forall g. g -> c g
z TcType -> HsWrapper
WpTyApp c (TcType -> HsWrapper) -> TcType -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
`k` TcType
a1
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
k forall g. g -> c g
z (WpLet TcEvBinds
a1) = (TcEvBinds -> HsWrapper) -> c (TcEvBinds -> HsWrapper)
forall g. g -> c g
z TcEvBinds -> HsWrapper
WpLet c (TcEvBinds -> HsWrapper) -> TcEvBinds -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
`k` TcEvBinds
a1
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsWrapper
gunfold forall b r. Data b => c (b -> r) -> c r
k forall r. r -> c r
z Constr
c = case Constr -> BranchIndex
Data.constrIndex Constr
c of
BranchIndex
1 -> HsWrapper -> c HsWrapper
forall r. r -> c r
z HsWrapper
WpHole
BranchIndex
2 -> c (HsWrapper -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
k (c (HsWrapper -> HsWrapper -> HsWrapper)
-> c (HsWrapper -> HsWrapper)
forall b r. Data b => c (b -> r) -> c r
k ((HsWrapper -> HsWrapper -> HsWrapper)
-> c (HsWrapper -> HsWrapper -> HsWrapper)
forall r. r -> c r
z HsWrapper -> HsWrapper -> HsWrapper
WpCompose))
BranchIndex
3 -> c (TcType -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
k (c (HsWrapper -> TcType -> HsWrapper) -> c (TcType -> HsWrapper)
forall b r. Data b => c (b -> r) -> c r
k (c (HsWrapper -> HsWrapper -> TcType -> HsWrapper)
-> c (HsWrapper -> TcType -> HsWrapper)
forall b r. Data b => c (b -> r) -> c r
k ((HsWrapper -> HsWrapper -> TcType -> HsWrapper)
-> c (HsWrapper -> HsWrapper -> TcType -> HsWrapper)
forall r. r -> c r
z HsWrapper -> HsWrapper -> TcType -> HsWrapper
wpFunEmpty)))
BranchIndex
4 -> c (TcCoercion -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
k ((TcCoercion -> HsWrapper) -> c (TcCoercion -> HsWrapper)
forall r. r -> c r
z TcCoercion -> HsWrapper
WpCast)
BranchIndex
5 -> c (TyVar -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
k ((TyVar -> HsWrapper) -> c (TyVar -> HsWrapper)
forall r. r -> c r
z TyVar -> HsWrapper
WpEvLam)
BranchIndex
6 -> c (EvTerm -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
k ((EvTerm -> HsWrapper) -> c (EvTerm -> HsWrapper)
forall r. r -> c r
z EvTerm -> HsWrapper
WpEvApp)
BranchIndex
7 -> c (TyVar -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
k ((TyVar -> HsWrapper) -> c (TyVar -> HsWrapper)
forall r. r -> c r
z TyVar -> HsWrapper
WpTyLam)
BranchIndex
8 -> c (TcType -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
k ((TcType -> HsWrapper) -> c (TcType -> HsWrapper)
forall r. r -> c r
z TcType -> HsWrapper
WpTyApp)
BranchIndex
_ -> c (TcEvBinds -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
k ((TcEvBinds -> HsWrapper) -> c (TcEvBinds -> HsWrapper)
forall r. r -> c r
z TcEvBinds -> HsWrapper
WpLet)
toConstr :: HsWrapper -> Constr
toConstr HsWrapper
WpHole = Constr
wpHole_constr
toConstr (WpCompose HsWrapper
_ HsWrapper
_) = Constr
wpCompose_constr
toConstr (WpFun HsWrapper
_ HsWrapper
_ TcType
_ SDoc
_) = Constr
wpFun_constr
toConstr (WpCast TcCoercion
_) = Constr
wpCast_constr
toConstr (WpEvLam TyVar
_) = Constr
wpEvLam_constr
toConstr (WpEvApp EvTerm
_) = Constr
wpEvApp_constr
toConstr (WpTyLam TyVar
_) = Constr
wpTyLam_constr
toConstr (WpTyApp TcType
_) = Constr
wpTyApp_constr
toConstr (WpLet TcEvBinds
_) = Constr
wpLet_constr
dataTypeOf :: HsWrapper -> DataType
dataTypeOf HsWrapper
_ = DataType
hsWrapper_dataType
hsWrapper_dataType :: Data.DataType
hsWrapper_dataType :: DataType
hsWrapper_dataType
= String -> [Constr] -> DataType
Data.mkDataType String
"HsWrapper"
[ Constr
wpHole_constr, Constr
wpCompose_constr, Constr
wpFun_constr, Constr
wpCast_constr
, Constr
wpEvLam_constr, Constr
wpEvApp_constr, Constr
wpTyLam_constr, Constr
wpTyApp_constr
, Constr
wpLet_constr]
wpHole_constr, wpCompose_constr, wpFun_constr, wpCast_constr, wpEvLam_constr,
wpEvApp_constr, wpTyLam_constr, wpTyApp_constr, wpLet_constr :: Data.Constr
wpHole_constr :: Constr
wpHole_constr = String -> Constr
mkHsWrapperConstr String
"WpHole"
wpCompose_constr :: Constr
wpCompose_constr = String -> Constr
mkHsWrapperConstr String
"WpCompose"
wpFun_constr :: Constr
wpFun_constr = String -> Constr
mkHsWrapperConstr String
"WpFun"
wpCast_constr :: Constr
wpCast_constr = String -> Constr
mkHsWrapperConstr String
"WpCast"
wpEvLam_constr :: Constr
wpEvLam_constr = String -> Constr
mkHsWrapperConstr String
"WpEvLam"
wpEvApp_constr :: Constr
wpEvApp_constr = String -> Constr
mkHsWrapperConstr String
"WpEvApp"
wpTyLam_constr :: Constr
wpTyLam_constr = String -> Constr
mkHsWrapperConstr String
"WpTyLam"
wpTyApp_constr :: Constr
wpTyApp_constr = String -> Constr
mkHsWrapperConstr String
"WpTyApp"
wpLet_constr :: Constr
wpLet_constr = String -> Constr
mkHsWrapperConstr String
"WpLet"
mkHsWrapperConstr :: String -> Data.Constr
mkHsWrapperConstr :: String -> Constr
mkHsWrapperConstr String
name = DataType -> String -> [String] -> Fixity -> Constr
Data.mkConstr DataType
hsWrapper_dataType String
name [] Fixity
Data.Prefix
wpFunEmpty :: HsWrapper -> HsWrapper -> TcType -> HsWrapper
wpFunEmpty :: HsWrapper -> HsWrapper -> TcType -> HsWrapper
wpFunEmpty HsWrapper
c1 HsWrapper
c2 TcType
t1 = HsWrapper -> HsWrapper -> TcType -> SDoc -> HsWrapper
WpFun HsWrapper
c1 HsWrapper
c2 TcType
t1 SDoc
empty
(<.>) :: HsWrapper -> HsWrapper -> HsWrapper
HsWrapper
WpHole <.> :: HsWrapper -> HsWrapper -> HsWrapper
<.> HsWrapper
c = HsWrapper
c
HsWrapper
c <.> HsWrapper
WpHole = HsWrapper
c
HsWrapper
c1 <.> HsWrapper
c2 = HsWrapper
c1 HsWrapper -> HsWrapper -> HsWrapper
`WpCompose` HsWrapper
c2
mkWpFun :: HsWrapper -> HsWrapper
-> TcType
-> TcType
-> SDoc
-> HsWrapper
mkWpFun :: HsWrapper -> HsWrapper -> TcType -> TcType -> SDoc -> HsWrapper
mkWpFun HsWrapper
WpHole HsWrapper
WpHole TcType
_ TcType
_ SDoc
_ = HsWrapper
WpHole
mkWpFun HsWrapper
WpHole (WpCast TcCoercion
co2) TcType
t1 TcType
_ SDoc
_ = TcCoercion -> HsWrapper
WpCast (Role -> TcCoercion -> TcCoercion -> TcCoercion
mkTcFunCo Role
Representational (TcType -> TcCoercion
mkTcRepReflCo TcType
t1) TcCoercion
co2)
mkWpFun (WpCast TcCoercion
co1) HsWrapper
WpHole TcType
_ TcType
t2 SDoc
_ = TcCoercion -> HsWrapper
WpCast (Role -> TcCoercion -> TcCoercion -> TcCoercion
mkTcFunCo Role
Representational (TcCoercion -> TcCoercion
mkTcSymCo TcCoercion
co1) (TcType -> TcCoercion
mkTcRepReflCo TcType
t2))
mkWpFun (WpCast TcCoercion
co1) (WpCast TcCoercion
co2) TcType
_ TcType
_ SDoc
_ = TcCoercion -> HsWrapper
WpCast (Role -> TcCoercion -> TcCoercion -> TcCoercion
mkTcFunCo Role
Representational (TcCoercion -> TcCoercion
mkTcSymCo TcCoercion
co1) TcCoercion
co2)
mkWpFun HsWrapper
co1 HsWrapper
co2 TcType
t1 TcType
_ SDoc
d = HsWrapper -> HsWrapper -> TcType -> SDoc -> HsWrapper
WpFun HsWrapper
co1 HsWrapper
co2 TcType
t1 SDoc
d
mkWpCastR :: TcCoercionR -> HsWrapper
mkWpCastR :: TcCoercion -> HsWrapper
mkWpCastR TcCoercion
co
| TcCoercion -> Bool
isTcReflCo TcCoercion
co = HsWrapper
WpHole
| Bool
otherwise = ASSERT2(tcCoercionRole co == Representational, ppr co)
TcCoercion -> HsWrapper
WpCast TcCoercion
co
mkWpCastN :: TcCoercionN -> HsWrapper
mkWpCastN :: TcCoercion -> HsWrapper
mkWpCastN TcCoercion
co
| TcCoercion -> Bool
isTcReflCo TcCoercion
co = HsWrapper
WpHole
| Bool
otherwise = ASSERT2(tcCoercionRole co == Nominal, ppr co)
TcCoercion -> HsWrapper
WpCast (TcCoercion -> TcCoercion
mkTcSubCo TcCoercion
co)
mkWpTyApps :: [Type] -> HsWrapper
mkWpTyApps :: [TcType] -> HsWrapper
mkWpTyApps [TcType]
tys = (TcType -> HsWrapper) -> [TcType] -> HsWrapper
forall a. (a -> HsWrapper) -> [a] -> HsWrapper
mk_co_app_fn TcType -> HsWrapper
WpTyApp [TcType]
tys
mkWpEvApps :: [EvTerm] -> HsWrapper
mkWpEvApps :: [EvTerm] -> HsWrapper
mkWpEvApps [EvTerm]
args = (EvTerm -> HsWrapper) -> [EvTerm] -> HsWrapper
forall a. (a -> HsWrapper) -> [a] -> HsWrapper
mk_co_app_fn EvTerm -> HsWrapper
WpEvApp [EvTerm]
args
mkWpEvVarApps :: [EvVar] -> HsWrapper
mkWpEvVarApps :: [TyVar] -> HsWrapper
mkWpEvVarApps [TyVar]
vs = (EvTerm -> HsWrapper) -> [EvTerm] -> HsWrapper
forall a. (a -> HsWrapper) -> [a] -> HsWrapper
mk_co_app_fn EvTerm -> HsWrapper
WpEvApp ((TyVar -> EvTerm) -> [TyVar] -> [EvTerm]
forall a b. (a -> b) -> [a] -> [b]
map (EvExpr -> EvTerm
EvExpr (EvExpr -> EvTerm) -> (TyVar -> EvExpr) -> TyVar -> EvTerm
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyVar -> EvExpr
evId) [TyVar]
vs)
mkWpTyLams :: [TyVar] -> HsWrapper
mkWpTyLams :: [TyVar] -> HsWrapper
mkWpTyLams [TyVar]
ids = (TyVar -> HsWrapper) -> [TyVar] -> HsWrapper
forall a. (a -> HsWrapper) -> [a] -> HsWrapper
mk_co_lam_fn TyVar -> HsWrapper
WpTyLam [TyVar]
ids
mkWpLams :: [Var] -> HsWrapper
mkWpLams :: [TyVar] -> HsWrapper
mkWpLams [TyVar]
ids = (TyVar -> HsWrapper) -> [TyVar] -> HsWrapper
forall a. (a -> HsWrapper) -> [a] -> HsWrapper
mk_co_lam_fn TyVar -> HsWrapper
WpEvLam [TyVar]
ids
mkWpLet :: TcEvBinds -> HsWrapper
mkWpLet :: TcEvBinds -> HsWrapper
mkWpLet (EvBinds Bag EvBind
b) | Bag EvBind -> Bool
forall a. Bag a -> Bool
isEmptyBag Bag EvBind
b = HsWrapper
WpHole
mkWpLet TcEvBinds
ev_binds = TcEvBinds -> HsWrapper
WpLet TcEvBinds
ev_binds
mk_co_lam_fn :: (a -> HsWrapper) -> [a] -> HsWrapper
mk_co_lam_fn :: (a -> HsWrapper) -> [a] -> HsWrapper
mk_co_lam_fn a -> HsWrapper
f [a]
as = (a -> HsWrapper -> HsWrapper) -> HsWrapper -> [a] -> HsWrapper
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\a
x HsWrapper
wrap -> a -> HsWrapper
f a
x HsWrapper -> HsWrapper -> HsWrapper
<.> HsWrapper
wrap) HsWrapper
WpHole [a]
as
mk_co_app_fn :: (a -> HsWrapper) -> [a] -> HsWrapper
mk_co_app_fn :: (a -> HsWrapper) -> [a] -> HsWrapper
mk_co_app_fn a -> HsWrapper
f [a]
as = (a -> HsWrapper -> HsWrapper) -> HsWrapper -> [a] -> HsWrapper
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\a
x HsWrapper
wrap -> HsWrapper
wrap HsWrapper -> HsWrapper -> HsWrapper
<.> a -> HsWrapper
f a
x) HsWrapper
WpHole [a]
as
idHsWrapper :: HsWrapper
idHsWrapper :: HsWrapper
idHsWrapper = HsWrapper
WpHole
isIdHsWrapper :: HsWrapper -> Bool
isIdHsWrapper :: HsWrapper -> Bool
isIdHsWrapper HsWrapper
WpHole = Bool
True
isIdHsWrapper HsWrapper
_ = Bool
False
isErasableHsWrapper :: HsWrapper -> Bool
isErasableHsWrapper :: HsWrapper -> Bool
isErasableHsWrapper = HsWrapper -> Bool
go
where
go :: HsWrapper -> Bool
go HsWrapper
WpHole = Bool
True
go (WpCompose HsWrapper
wrap1 HsWrapper
wrap2) = HsWrapper -> Bool
go HsWrapper
wrap1 Bool -> Bool -> Bool
&& HsWrapper -> Bool
go HsWrapper
wrap2
go WpFun{} = Bool
False
go WpCast{} = Bool
True
go WpEvLam{} = Bool
False
go WpEvApp{} = Bool
False
go WpTyLam{} = Bool
True
go WpTyApp{} = Bool
True
go WpLet{} = Bool
False
collectHsWrapBinders :: HsWrapper -> ([Var], HsWrapper)
collectHsWrapBinders :: HsWrapper -> ([TyVar], HsWrapper)
collectHsWrapBinders HsWrapper
wrap = HsWrapper -> [HsWrapper] -> ([TyVar], HsWrapper)
go HsWrapper
wrap []
where
go :: HsWrapper -> [HsWrapper] -> ([Var], HsWrapper)
go :: HsWrapper -> [HsWrapper] -> ([TyVar], HsWrapper)
go (WpEvLam TyVar
v) [HsWrapper]
wraps = TyVar -> ([TyVar], HsWrapper) -> ([TyVar], HsWrapper)
forall a b. a -> ([a], b) -> ([a], b)
add_lam TyVar
v ([HsWrapper] -> ([TyVar], HsWrapper)
gos [HsWrapper]
wraps)
go (WpTyLam TyVar
v) [HsWrapper]
wraps = TyVar -> ([TyVar], HsWrapper) -> ([TyVar], HsWrapper)
forall a b. a -> ([a], b) -> ([a], b)
add_lam TyVar
v ([HsWrapper] -> ([TyVar], HsWrapper)
gos [HsWrapper]
wraps)
go (WpCompose HsWrapper
w1 HsWrapper
w2) [HsWrapper]
wraps = HsWrapper -> [HsWrapper] -> ([TyVar], HsWrapper)
go HsWrapper
w1 (HsWrapper
w2HsWrapper -> [HsWrapper] -> [HsWrapper]
forall a. a -> [a] -> [a]
:[HsWrapper]
wraps)
go HsWrapper
wrap [HsWrapper]
wraps = ([], (HsWrapper -> HsWrapper -> HsWrapper)
-> HsWrapper -> [HsWrapper] -> HsWrapper
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' HsWrapper -> HsWrapper -> HsWrapper
(<.>) HsWrapper
wrap [HsWrapper]
wraps)
gos :: [HsWrapper] -> ([TyVar], HsWrapper)
gos [] = ([], HsWrapper
WpHole)
gos (HsWrapper
w:[HsWrapper]
ws) = HsWrapper -> [HsWrapper] -> ([TyVar], HsWrapper)
go HsWrapper
w [HsWrapper]
ws
add_lam :: a -> ([a], b) -> ([a], b)
add_lam a
v ([a]
vs,b
w) = (a
va -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
vs, b
w)
data TcEvBinds
= TcEvBinds
EvBindsVar
| EvBinds
(Bag EvBind)
data EvBindsVar
= EvBindsVar {
EvBindsVar -> Unique
ebv_uniq :: Unique,
EvBindsVar -> IORef EvBindMap
ebv_binds :: IORef EvBindMap,
EvBindsVar -> IORef TcTyCoVarSet
ebv_tcvs :: IORef CoVarSet
}
| CoEvBindsVar {
ebv_uniq :: Unique,
ebv_tcvs :: IORef CoVarSet
}
instance Data.Data TcEvBinds where
toConstr :: TcEvBinds -> Constr
toConstr TcEvBinds
_ = String -> Constr
abstractConstr String
"TcEvBinds"
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TcEvBinds
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_ = String -> Constr -> c TcEvBinds
forall a. HasCallStack => String -> a
error String
"gunfold"
dataTypeOf :: TcEvBinds -> DataType
dataTypeOf TcEvBinds
_ = String -> DataType
Data.mkNoRepType String
"TcEvBinds"
isCoEvBindsVar :: EvBindsVar -> Bool
isCoEvBindsVar :: EvBindsVar -> Bool
isCoEvBindsVar (CoEvBindsVar {}) = Bool
True
isCoEvBindsVar (EvBindsVar {}) = Bool
False
newtype EvBindMap
= EvBindMap {
EvBindMap -> DVarEnv EvBind
ev_bind_varenv :: DVarEnv EvBind
}
emptyEvBindMap :: EvBindMap
emptyEvBindMap :: EvBindMap
emptyEvBindMap = EvBindMap :: DVarEnv EvBind -> EvBindMap
EvBindMap { ev_bind_varenv :: DVarEnv EvBind
ev_bind_varenv = DVarEnv EvBind
forall a. DVarEnv a
emptyDVarEnv }
extendEvBinds :: EvBindMap -> EvBind -> EvBindMap
extendEvBinds :: EvBindMap -> EvBind -> EvBindMap
extendEvBinds EvBindMap
bs EvBind
ev_bind
= EvBindMap :: DVarEnv EvBind -> EvBindMap
EvBindMap { ev_bind_varenv :: DVarEnv EvBind
ev_bind_varenv = DVarEnv EvBind -> TyVar -> EvBind -> DVarEnv EvBind
forall a. DVarEnv a -> TyVar -> a -> DVarEnv a
extendDVarEnv (EvBindMap -> DVarEnv EvBind
ev_bind_varenv EvBindMap
bs)
(EvBind -> TyVar
eb_lhs EvBind
ev_bind)
EvBind
ev_bind }
isEmptyEvBindMap :: EvBindMap -> Bool
isEmptyEvBindMap :: EvBindMap -> Bool
isEmptyEvBindMap (EvBindMap DVarEnv EvBind
m) = DVarEnv EvBind -> Bool
forall a. DVarEnv a -> Bool
isEmptyDVarEnv DVarEnv EvBind
m
lookupEvBind :: EvBindMap -> EvVar -> Maybe EvBind
lookupEvBind :: EvBindMap -> TyVar -> Maybe EvBind
lookupEvBind EvBindMap
bs = DVarEnv EvBind -> TyVar -> Maybe EvBind
forall a. DVarEnv a -> TyVar -> Maybe a
lookupDVarEnv (EvBindMap -> DVarEnv EvBind
ev_bind_varenv EvBindMap
bs)
evBindMapBinds :: EvBindMap -> Bag EvBind
evBindMapBinds :: EvBindMap -> Bag EvBind
evBindMapBinds = (EvBind -> Bag EvBind -> Bag EvBind)
-> Bag EvBind -> EvBindMap -> Bag EvBind
forall a. (EvBind -> a -> a) -> a -> EvBindMap -> a
foldEvBindMap EvBind -> Bag EvBind -> Bag EvBind
forall a. a -> Bag a -> Bag a
consBag Bag EvBind
forall a. Bag a
emptyBag
foldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a
foldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a
foldEvBindMap EvBind -> a -> a
k a
z EvBindMap
bs = (EvBind -> a -> a) -> a -> DVarEnv EvBind -> a
forall a b. (a -> b -> b) -> b -> DVarEnv a -> b
foldDVarEnv EvBind -> a -> a
k a
z (EvBindMap -> DVarEnv EvBind
ev_bind_varenv EvBindMap
bs)
filterEvBindMap :: (EvBind -> Bool) -> EvBindMap -> EvBindMap
filterEvBindMap :: (EvBind -> Bool) -> EvBindMap -> EvBindMap
filterEvBindMap EvBind -> Bool
k (EvBindMap { ev_bind_varenv :: EvBindMap -> DVarEnv EvBind
ev_bind_varenv = DVarEnv EvBind
env })
= EvBindMap :: DVarEnv EvBind -> EvBindMap
EvBindMap { ev_bind_varenv :: DVarEnv EvBind
ev_bind_varenv = (EvBind -> Bool) -> DVarEnv EvBind -> DVarEnv EvBind
forall a. (a -> Bool) -> DVarEnv a -> DVarEnv a
filterDVarEnv EvBind -> Bool
k DVarEnv EvBind
env }
instance Outputable EvBindMap where
ppr :: EvBindMap -> SDoc
ppr (EvBindMap DVarEnv EvBind
m) = DVarEnv EvBind -> SDoc
forall a. Outputable a => a -> SDoc
ppr DVarEnv EvBind
m
data EvBind
= EvBind { EvBind -> TyVar
eb_lhs :: EvVar
, EvBind -> EvTerm
eb_rhs :: EvTerm
, EvBind -> Bool
eb_is_given :: Bool
}
evBindVar :: EvBind -> EvVar
evBindVar :: EvBind -> TyVar
evBindVar = EvBind -> TyVar
eb_lhs
mkWantedEvBind :: EvVar -> EvTerm -> EvBind
mkWantedEvBind :: TyVar -> EvTerm -> EvBind
mkWantedEvBind TyVar
ev EvTerm
tm = EvBind :: TyVar -> EvTerm -> Bool -> EvBind
EvBind { eb_is_given :: Bool
eb_is_given = Bool
False, eb_lhs :: TyVar
eb_lhs = TyVar
ev, eb_rhs :: EvTerm
eb_rhs = EvTerm
tm }
mkGivenEvBind :: EvVar -> EvTerm -> EvBind
mkGivenEvBind :: TyVar -> EvTerm -> EvBind
mkGivenEvBind TyVar
ev EvTerm
tm = EvBind :: TyVar -> EvTerm -> Bool -> EvBind
EvBind { eb_is_given :: Bool
eb_is_given = Bool
True, eb_lhs :: TyVar
eb_lhs = TyVar
ev, eb_rhs :: EvTerm
eb_rhs = EvTerm
tm }
data EvTerm
= EvExpr EvExpr
| EvTypeable Type EvTypeable
| EvFun
{ EvTerm -> [TyVar]
et_tvs :: [TyVar]
, EvTerm -> [TyVar]
et_given :: [EvVar]
, EvTerm -> TcEvBinds
et_binds :: TcEvBinds
, EvTerm -> TyVar
et_body :: EvVar }
deriving Typeable EvTerm
DataType
Constr
Typeable EvTerm
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvTerm -> c EvTerm)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvTerm)
-> (EvTerm -> Constr)
-> (EvTerm -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EvTerm))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTerm))
-> ((forall b. Data b => b -> b) -> EvTerm -> EvTerm)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EvTerm -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EvTerm -> r)
-> (forall u. (forall d. Data d => d -> u) -> EvTerm -> [u])
-> (forall u.
BranchIndex -> (forall d. Data d => d -> u) -> EvTerm -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EvTerm -> m EvTerm)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvTerm -> m EvTerm)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvTerm -> m EvTerm)
-> Data EvTerm
EvTerm -> DataType
EvTerm -> Constr
(forall b. Data b => b -> b) -> EvTerm -> EvTerm
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvTerm -> c EvTerm
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvTerm
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u.
BranchIndex -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
BranchIndex -> (forall d. Data d => d -> u) -> EvTerm -> u
forall u. (forall d. Data d => d -> u) -> EvTerm -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EvTerm -> m EvTerm
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvTerm -> m EvTerm
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvTerm
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvTerm -> c EvTerm
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EvTerm)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTerm)
$cEvFun :: Constr
$cEvTypeable :: Constr
$cEvExpr :: Constr
$tEvTerm :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvTerm -> m EvTerm
gmapMp :: (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvTerm -> m EvTerm
gmapM :: (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EvTerm -> m EvTerm
gmapQi :: BranchIndex -> (forall d. Data d => d -> u) -> EvTerm -> u
$cgmapQi :: forall u.
BranchIndex -> (forall d. Data d => d -> u) -> EvTerm -> u
gmapQ :: (forall d. Data d => d -> u) -> EvTerm -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> EvTerm -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r
gmapT :: (forall b. Data b => b -> b) -> EvTerm -> EvTerm
$cgmapT :: (forall b. Data b => b -> b) -> EvTerm -> EvTerm
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTerm)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTerm)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c EvTerm)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EvTerm)
dataTypeOf :: EvTerm -> DataType
$cdataTypeOf :: EvTerm -> DataType
toConstr :: EvTerm -> Constr
$ctoConstr :: EvTerm -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvTerm
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvTerm
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvTerm -> c EvTerm
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvTerm -> c EvTerm
$cp1Data :: Typeable EvTerm
Data.Data
type EvExpr = CoreExpr
evId :: EvId -> EvExpr
evId :: TyVar -> EvExpr
evId = TyVar -> EvExpr
forall b. TyVar -> Expr b
Var
evCoercion :: TcCoercion -> EvTerm
evCoercion :: TcCoercion -> EvTerm
evCoercion TcCoercion
co = EvExpr -> EvTerm
EvExpr (TcCoercion -> EvExpr
forall b. TcCoercion -> Expr b
Coercion TcCoercion
co)
evCast :: EvExpr -> TcCoercion -> EvTerm
evCast :: EvExpr -> TcCoercion -> EvTerm
evCast EvExpr
et TcCoercion
tc | TcCoercion -> Bool
isReflCo TcCoercion
tc = EvExpr -> EvTerm
EvExpr EvExpr
et
| Bool
otherwise = EvExpr -> EvTerm
EvExpr (EvExpr -> TcCoercion -> EvExpr
forall b. Expr b -> TcCoercion -> Expr b
Cast EvExpr
et TcCoercion
tc)
evDFunApp :: DFunId -> [Type] -> [EvExpr] -> EvTerm
evDFunApp :: TyVar -> [TcType] -> [EvExpr] -> EvTerm
evDFunApp TyVar
df [TcType]
tys [EvExpr]
ets = EvExpr -> EvTerm
EvExpr (EvExpr -> EvTerm) -> EvExpr -> EvTerm
forall a b. (a -> b) -> a -> b
$ TyVar -> EvExpr
forall b. TyVar -> Expr b
Var TyVar
df EvExpr -> [TcType] -> EvExpr
forall b. Expr b -> [TcType] -> Expr b
`mkTyApps` [TcType]
tys EvExpr -> [EvExpr] -> EvExpr
forall b. Expr b -> [Expr b] -> Expr b
`mkApps` [EvExpr]
ets
evDataConApp :: DataCon -> [Type] -> [EvExpr] -> EvTerm
evDataConApp :: DataCon -> [TcType] -> [EvExpr] -> EvTerm
evDataConApp DataCon
dc [TcType]
tys [EvExpr]
ets = TyVar -> [TcType] -> [EvExpr] -> EvTerm
evDFunApp (DataCon -> TyVar
dataConWrapId DataCon
dc) [TcType]
tys [EvExpr]
ets
evSelector :: Id -> [Type] -> [EvExpr] -> EvExpr
evSelector :: TyVar -> [TcType] -> [EvExpr] -> EvExpr
evSelector TyVar
sel_id [TcType]
tys [EvExpr]
tms = TyVar -> EvExpr
forall b. TyVar -> Expr b
Var TyVar
sel_id EvExpr -> [TcType] -> EvExpr
forall b. Expr b -> [TcType] -> Expr b
`mkTyApps` [TcType]
tys EvExpr -> [EvExpr] -> EvExpr
forall b. Expr b -> [Expr b] -> Expr b
`mkApps` [EvExpr]
tms
evTypeable :: Type -> EvTypeable -> EvTerm
evTypeable :: TcType -> EvTypeable -> EvTerm
evTypeable = TcType -> EvTypeable -> EvTerm
EvTypeable
data EvTypeable
= EvTypeableTyCon TyCon [EvTerm]
| EvTypeableTyApp EvTerm EvTerm
| EvTypeableTrFun EvTerm EvTerm
| EvTypeableTyLit EvTerm
deriving Typeable EvTypeable
DataType
Constr
Typeable EvTypeable
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvTypeable -> c EvTypeable)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvTypeable)
-> (EvTypeable -> Constr)
-> (EvTypeable -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EvTypeable))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EvTypeable))
-> ((forall b. Data b => b -> b) -> EvTypeable -> EvTypeable)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EvTypeable -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EvTypeable -> r)
-> (forall u. (forall d. Data d => d -> u) -> EvTypeable -> [u])
-> (forall u.
BranchIndex -> (forall d. Data d => d -> u) -> EvTypeable -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable)
-> Data EvTypeable
EvTypeable -> DataType
EvTypeable -> Constr
(forall b. Data b => b -> b) -> EvTypeable -> EvTypeable
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvTypeable -> c EvTypeable
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvTypeable
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u.
BranchIndex -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
BranchIndex -> (forall d. Data d => d -> u) -> EvTypeable -> u
forall u. (forall d. Data d => d -> u) -> EvTypeable -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EvTypeable -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EvTypeable -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvTypeable
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvTypeable -> c EvTypeable
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EvTypeable)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTypeable)
$cEvTypeableTyLit :: Constr
$cEvTypeableTrFun :: Constr
$cEvTypeableTyApp :: Constr
$cEvTypeableTyCon :: Constr
$tEvTypeable :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable
gmapMp :: (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable
gmapM :: (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable
gmapQi :: BranchIndex -> (forall d. Data d => d -> u) -> EvTypeable -> u
$cgmapQi :: forall u.
BranchIndex -> (forall d. Data d => d -> u) -> EvTypeable -> u
gmapQ :: (forall d. Data d => d -> u) -> EvTypeable -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> EvTypeable -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EvTypeable -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EvTypeable -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EvTypeable -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EvTypeable -> r
gmapT :: (forall b. Data b => b -> b) -> EvTypeable -> EvTypeable
$cgmapT :: (forall b. Data b => b -> b) -> EvTypeable -> EvTypeable
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTypeable)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTypeable)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c EvTypeable)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EvTypeable)
dataTypeOf :: EvTypeable -> DataType
$cdataTypeOf :: EvTypeable -> DataType
toConstr :: EvTypeable -> Constr
$ctoConstr :: EvTypeable -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvTypeable
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvTypeable
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvTypeable -> c EvTypeable
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvTypeable -> c EvTypeable
$cp1Data :: Typeable EvTypeable
Data.Data
data EvCallStack
= EvCsEmpty
| EvCsPushCall Name RealSrcSpan EvExpr
deriving Typeable EvCallStack
DataType
Constr
Typeable EvCallStack
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvCallStack -> c EvCallStack)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvCallStack)
-> (EvCallStack -> Constr)
-> (EvCallStack -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EvCallStack))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EvCallStack))
-> ((forall b. Data b => b -> b) -> EvCallStack -> EvCallStack)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EvCallStack -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EvCallStack -> r)
-> (forall u. (forall d. Data d => d -> u) -> EvCallStack -> [u])
-> (forall u.
BranchIndex -> (forall d. Data d => d -> u) -> EvCallStack -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack)
-> Data EvCallStack
EvCallStack -> DataType
EvCallStack -> Constr
(forall b. Data b => b -> b) -> EvCallStack -> EvCallStack
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvCallStack -> c EvCallStack
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvCallStack
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u.
BranchIndex -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
BranchIndex -> (forall d. Data d => d -> u) -> EvCallStack -> u
forall u. (forall d. Data d => d -> u) -> EvCallStack -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EvCallStack -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EvCallStack -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvCallStack
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvCallStack -> c EvCallStack
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EvCallStack)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EvCallStack)
$cEvCsPushCall :: Constr
$cEvCsEmpty :: Constr
$tEvCallStack :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack
gmapMp :: (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack
gmapM :: (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack
gmapQi :: BranchIndex -> (forall d. Data d => d -> u) -> EvCallStack -> u
$cgmapQi :: forall u.
BranchIndex -> (forall d. Data d => d -> u) -> EvCallStack -> u
gmapQ :: (forall d. Data d => d -> u) -> EvCallStack -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> EvCallStack -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EvCallStack -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EvCallStack -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EvCallStack -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EvCallStack -> r
gmapT :: (forall b. Data b => b -> b) -> EvCallStack -> EvCallStack
$cgmapT :: (forall b. Data b => b -> b) -> EvCallStack -> EvCallStack
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EvCallStack)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EvCallStack)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c EvCallStack)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EvCallStack)
dataTypeOf :: EvCallStack -> DataType
$cdataTypeOf :: EvCallStack -> DataType
toConstr :: EvCallStack -> Constr
$ctoConstr :: EvCallStack -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvCallStack
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EvCallStack
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvCallStack -> c EvCallStack
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EvCallStack -> c EvCallStack
$cp1Data :: Typeable EvCallStack
Data.Data
mkEvCast :: EvExpr -> TcCoercion -> EvTerm
mkEvCast :: EvExpr -> TcCoercion -> EvTerm
mkEvCast EvExpr
ev TcCoercion
lco
| ASSERT2( tcCoercionRole lco == Representational
, (vcat [text "Coercion of wrong role passed to mkEvCast:", ppr ev, ppr lco]))
TcCoercion -> Bool
isTcReflCo TcCoercion
lco = EvExpr -> EvTerm
EvExpr EvExpr
ev
| Bool
otherwise = EvExpr -> TcCoercion -> EvTerm
evCast EvExpr
ev TcCoercion
lco
mkEvScSelectors
:: Class -> [TcType]
-> [(TcPredType,
EvExpr)
]
mkEvScSelectors :: Class -> [TcType] -> [(TcType, EvExpr)]
mkEvScSelectors Class
cls [TcType]
tys
= (TcType -> BranchIndex -> (TcType, EvExpr))
-> [TcType] -> [BranchIndex] -> [(TcType, EvExpr)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith TcType -> BranchIndex -> (TcType, EvExpr)
forall a b. a -> BranchIndex -> (a, Expr b)
mk_pr (Class -> [TcType] -> [TcType]
immSuperClasses Class
cls [TcType]
tys) [BranchIndex
0..]
where
mk_pr :: a -> BranchIndex -> (a, Expr b)
mk_pr a
pred BranchIndex
i = (a
pred, TyVar -> Expr b
forall b. TyVar -> Expr b
Var TyVar
sc_sel_id Expr b -> [TcType] -> Expr b
forall b. Expr b -> [TcType] -> Expr b
`mkTyApps` [TcType]
tys)
where
sc_sel_id :: TyVar
sc_sel_id = Class -> BranchIndex -> TyVar
classSCSelId Class
cls BranchIndex
i
emptyTcEvBinds :: TcEvBinds
emptyTcEvBinds :: TcEvBinds
emptyTcEvBinds = Bag EvBind -> TcEvBinds
EvBinds Bag EvBind
forall a. Bag a
emptyBag
isEmptyTcEvBinds :: TcEvBinds -> Bool
isEmptyTcEvBinds :: TcEvBinds -> Bool
isEmptyTcEvBinds (EvBinds Bag EvBind
b) = Bag EvBind -> Bool
forall a. Bag a -> Bool
isEmptyBag Bag EvBind
b
isEmptyTcEvBinds (TcEvBinds {}) = String -> Bool
forall a. String -> a
panic String
"isEmptyTcEvBinds"
evTermCoercion_maybe :: EvTerm -> Maybe TcCoercion
evTermCoercion_maybe :: EvTerm -> Maybe TcCoercion
evTermCoercion_maybe EvTerm
ev_term
| EvExpr EvExpr
e <- EvTerm
ev_term = EvExpr -> Maybe TcCoercion
go EvExpr
e
| Bool
otherwise = Maybe TcCoercion
forall a. Maybe a
Nothing
where
go :: EvExpr -> Maybe TcCoercion
go :: EvExpr -> Maybe TcCoercion
go (Var TyVar
v) = TcCoercion -> Maybe TcCoercion
forall (m :: * -> *) a. Monad m => a -> m a
return (TyVar -> TcCoercion
mkCoVarCo TyVar
v)
go (Coercion TcCoercion
co) = TcCoercion -> Maybe TcCoercion
forall (m :: * -> *) a. Monad m => a -> m a
return TcCoercion
co
go (Cast EvExpr
tm TcCoercion
co) = do { TcCoercion
co' <- EvExpr -> Maybe TcCoercion
go EvExpr
tm
; TcCoercion -> Maybe TcCoercion
forall (m :: * -> *) a. Monad m => a -> m a
return (TcCoercion -> TcCoercion -> TcCoercion
mkCoCast TcCoercion
co' TcCoercion
co) }
go EvExpr
_ = Maybe TcCoercion
forall a. Maybe a
Nothing
evTermCoercion :: EvTerm -> TcCoercion
evTermCoercion :: EvTerm -> TcCoercion
evTermCoercion EvTerm
tm = case EvTerm -> Maybe TcCoercion
evTermCoercion_maybe EvTerm
tm of
Just TcCoercion
co -> TcCoercion
co
Maybe TcCoercion
Nothing -> String -> SDoc -> TcCoercion
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"evTermCoercion" (EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
ppr EvTerm
tm)
findNeededEvVars :: EvBindMap -> VarSet -> VarSet
findNeededEvVars :: EvBindMap -> TcTyCoVarSet -> TcTyCoVarSet
findNeededEvVars EvBindMap
ev_binds TcTyCoVarSet
seeds
= (TcTyCoVarSet -> TcTyCoVarSet) -> TcTyCoVarSet -> TcTyCoVarSet
transCloVarSet TcTyCoVarSet -> TcTyCoVarSet
also_needs TcTyCoVarSet
seeds
where
also_needs :: VarSet -> VarSet
also_needs :: TcTyCoVarSet -> TcTyCoVarSet
also_needs TcTyCoVarSet
needs = (TyVar -> TcTyCoVarSet -> TcTyCoVarSet)
-> TcTyCoVarSet -> TcTyCoVarSet -> TcTyCoVarSet
forall elt a. (elt -> a -> a) -> a -> UniqSet elt -> a
nonDetFoldUniqSet TyVar -> TcTyCoVarSet -> TcTyCoVarSet
add TcTyCoVarSet
emptyVarSet TcTyCoVarSet
needs
add :: Var -> VarSet -> VarSet
add :: TyVar -> TcTyCoVarSet -> TcTyCoVarSet
add TyVar
v TcTyCoVarSet
needs
| Just EvBind
ev_bind <- EvBindMap -> TyVar -> Maybe EvBind
lookupEvBind EvBindMap
ev_binds TyVar
v
, EvBind { eb_is_given :: EvBind -> Bool
eb_is_given = Bool
is_given, eb_rhs :: EvBind -> EvTerm
eb_rhs = EvTerm
rhs } <- EvBind
ev_bind
, Bool
is_given
= EvTerm -> TcTyCoVarSet
evVarsOfTerm EvTerm
rhs TcTyCoVarSet -> TcTyCoVarSet -> TcTyCoVarSet
`unionVarSet` TcTyCoVarSet
needs
| Bool
otherwise
= TcTyCoVarSet
needs
evVarsOfTerm :: EvTerm -> VarSet
evVarsOfTerm :: EvTerm -> TcTyCoVarSet
evVarsOfTerm (EvExpr EvExpr
e) = InterestingVarFun -> EvExpr -> TcTyCoVarSet
exprSomeFreeVars InterestingVarFun
isEvVar EvExpr
e
evVarsOfTerm (EvTypeable TcType
_ EvTypeable
ev) = EvTypeable -> TcTyCoVarSet
evVarsOfTypeable EvTypeable
ev
evVarsOfTerm (EvFun {}) = TcTyCoVarSet
emptyVarSet
evVarsOfTerms :: [EvTerm] -> VarSet
evVarsOfTerms :: [EvTerm] -> TcTyCoVarSet
evVarsOfTerms = (EvTerm -> TcTyCoVarSet) -> [EvTerm] -> TcTyCoVarSet
forall a. (a -> TcTyCoVarSet) -> [a] -> TcTyCoVarSet
mapUnionVarSet EvTerm -> TcTyCoVarSet
evVarsOfTerm
evVarsOfTypeable :: EvTypeable -> VarSet
evVarsOfTypeable :: EvTypeable -> TcTyCoVarSet
evVarsOfTypeable EvTypeable
ev =
case EvTypeable
ev of
EvTypeableTyCon TyCon
_ [EvTerm]
e -> (EvTerm -> TcTyCoVarSet) -> [EvTerm] -> TcTyCoVarSet
forall a. (a -> TcTyCoVarSet) -> [a] -> TcTyCoVarSet
mapUnionVarSet EvTerm -> TcTyCoVarSet
evVarsOfTerm [EvTerm]
e
EvTypeableTyApp EvTerm
e1 EvTerm
e2 -> [EvTerm] -> TcTyCoVarSet
evVarsOfTerms [EvTerm
e1,EvTerm
e2]
EvTypeableTrFun EvTerm
e1 EvTerm
e2 -> [EvTerm] -> TcTyCoVarSet
evVarsOfTerms [EvTerm
e1,EvTerm
e2]
EvTypeableTyLit EvTerm
e -> EvTerm -> TcTyCoVarSet
evVarsOfTerm EvTerm
e
instance Outputable HsWrapper where
ppr :: HsWrapper -> SDoc
ppr HsWrapper
co_fn = HsWrapper -> (Bool -> SDoc) -> SDoc
pprHsWrapper HsWrapper
co_fn (SDoc -> Bool -> SDoc
no_parens (String -> SDoc
text String
"<>"))
pprHsWrapper :: HsWrapper -> (Bool -> SDoc) -> SDoc
pprHsWrapper :: HsWrapper -> (Bool -> SDoc) -> SDoc
pprHsWrapper HsWrapper
wrap Bool -> SDoc
pp_thing_inside
= (DynFlags -> SDoc) -> SDoc
sdocWithDynFlags ((DynFlags -> SDoc) -> SDoc) -> (DynFlags -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \ DynFlags
dflags ->
if GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_PrintTypecheckerElaboration DynFlags
dflags
then (Bool -> SDoc) -> HsWrapper -> Bool -> SDoc
help Bool -> SDoc
pp_thing_inside HsWrapper
wrap Bool
False
else Bool -> SDoc
pp_thing_inside Bool
False
where
help :: (Bool -> SDoc) -> HsWrapper -> Bool -> SDoc
help :: (Bool -> SDoc) -> HsWrapper -> Bool -> SDoc
help Bool -> SDoc
it HsWrapper
WpHole = Bool -> SDoc
it
help Bool -> SDoc
it (WpCompose HsWrapper
f1 HsWrapper
f2) = (Bool -> SDoc) -> HsWrapper -> Bool -> SDoc
help ((Bool -> SDoc) -> HsWrapper -> Bool -> SDoc
help Bool -> SDoc
it HsWrapper
f2) HsWrapper
f1
help Bool -> SDoc
it (WpFun HsWrapper
f1 HsWrapper
f2 TcType
t1 SDoc
_) = SDoc -> Bool -> SDoc
add_parens (SDoc -> Bool -> SDoc) -> SDoc -> Bool -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"\\(x" SDoc -> SDoc -> SDoc
<> SDoc
dcolon SDoc -> SDoc -> SDoc
<> TcType -> SDoc
forall a. Outputable a => a -> SDoc
ppr TcType
t1 SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
")." SDoc -> SDoc -> SDoc
<+>
(Bool -> SDoc) -> HsWrapper -> Bool -> SDoc
help (\Bool
_ -> Bool -> SDoc
it Bool
True SDoc -> SDoc -> SDoc
<+> (Bool -> SDoc) -> HsWrapper -> Bool -> SDoc
help (\Bool
_ -> String -> SDoc
text String
"x") HsWrapper
f1 Bool
True) HsWrapper
f2 Bool
False
help Bool -> SDoc
it (WpCast TcCoercion
co) = SDoc -> Bool -> SDoc
add_parens (SDoc -> Bool -> SDoc) -> SDoc -> Bool -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
sep [Bool -> SDoc
it Bool
False, BranchIndex -> SDoc -> SDoc
nest BranchIndex
2 (String -> SDoc
text String
"|>"
SDoc -> SDoc -> SDoc
<+> TcCoercion -> SDoc
pprParendCo TcCoercion
co)]
help Bool -> SDoc
it (WpEvApp EvTerm
id) = SDoc -> Bool -> SDoc
no_parens (SDoc -> Bool -> SDoc) -> SDoc -> Bool -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
sep [Bool -> SDoc
it Bool
True, BranchIndex -> SDoc -> SDoc
nest BranchIndex
2 (EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
ppr EvTerm
id)]
help Bool -> SDoc
it (WpTyApp TcType
ty) = SDoc -> Bool -> SDoc
no_parens (SDoc -> Bool -> SDoc) -> SDoc -> Bool -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
sep [Bool -> SDoc
it Bool
True, String -> SDoc
text String
"@" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
pprParendType TcType
ty]
help Bool -> SDoc
it (WpEvLam TyVar
id) = SDoc -> Bool -> SDoc
add_parens (SDoc -> Bool -> SDoc) -> SDoc -> Bool -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
sep [ String -> SDoc
text String
"\\" SDoc -> SDoc -> SDoc
<> TyVar -> SDoc
pprLamBndr TyVar
id SDoc -> SDoc -> SDoc
<> SDoc
dot, Bool -> SDoc
it Bool
False]
help Bool -> SDoc
it (WpTyLam TyVar
tv) = SDoc -> Bool -> SDoc
add_parens (SDoc -> Bool -> SDoc) -> SDoc -> Bool -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
sep [String -> SDoc
text String
"/\\" SDoc -> SDoc -> SDoc
<> TyVar -> SDoc
pprLamBndr TyVar
tv SDoc -> SDoc -> SDoc
<> SDoc
dot, Bool -> SDoc
it Bool
False]
help Bool -> SDoc
it (WpLet TcEvBinds
binds) = SDoc -> Bool -> SDoc
add_parens (SDoc -> Bool -> SDoc) -> SDoc -> Bool -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
sep [String -> SDoc
text String
"let" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
braces (TcEvBinds -> SDoc
forall a. Outputable a => a -> SDoc
ppr TcEvBinds
binds), Bool -> SDoc
it Bool
False]
pprLamBndr :: Id -> SDoc
pprLamBndr :: TyVar -> SDoc
pprLamBndr TyVar
v = BindingSite -> TyVar -> SDoc
forall a. OutputableBndr a => BindingSite -> a -> SDoc
pprBndr BindingSite
LambdaBind TyVar
v
add_parens, no_parens :: SDoc -> Bool -> SDoc
add_parens :: SDoc -> Bool -> SDoc
add_parens SDoc
d Bool
True = SDoc -> SDoc
parens SDoc
d
add_parens SDoc
d Bool
False = SDoc
d
no_parens :: SDoc -> Bool -> SDoc
no_parens SDoc
d Bool
_ = SDoc
d
instance Outputable TcEvBinds where
ppr :: TcEvBinds -> SDoc
ppr (TcEvBinds EvBindsVar
v) = EvBindsVar -> SDoc
forall a. Outputable a => a -> SDoc
ppr EvBindsVar
v
ppr (EvBinds Bag EvBind
bs) = String -> SDoc
text String
"EvBinds" SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
braces ([SDoc] -> SDoc
vcat ((EvBind -> SDoc) -> [EvBind] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map EvBind -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Bag EvBind -> [EvBind]
forall a. Bag a -> [a]
bagToList Bag EvBind
bs)))
instance Outputable EvBindsVar where
ppr :: EvBindsVar -> SDoc
ppr (EvBindsVar { ebv_uniq :: EvBindsVar -> Unique
ebv_uniq = Unique
u })
= String -> SDoc
text String
"EvBindsVar" SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
angleBrackets (Unique -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unique
u)
ppr (CoEvBindsVar { ebv_uniq :: EvBindsVar -> Unique
ebv_uniq = Unique
u })
= String -> SDoc
text String
"CoEvBindsVar" SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
angleBrackets (Unique -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unique
u)
instance Uniquable EvBindsVar where
getUnique :: EvBindsVar -> Unique
getUnique = EvBindsVar -> Unique
ebv_uniq
instance Outputable EvBind where
ppr :: EvBind -> SDoc
ppr (EvBind { eb_lhs :: EvBind -> TyVar
eb_lhs = TyVar
v, eb_rhs :: EvBind -> EvTerm
eb_rhs = EvTerm
e, eb_is_given :: EvBind -> Bool
eb_is_given = Bool
is_given })
= [SDoc] -> SDoc
sep [ SDoc
pp_gw SDoc -> SDoc -> SDoc
<+> TyVar -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyVar
v
, BranchIndex -> SDoc -> SDoc
nest BranchIndex
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc
equals SDoc -> SDoc -> SDoc
<+> EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
ppr EvTerm
e ]
where
pp_gw :: SDoc
pp_gw = SDoc -> SDoc
brackets (if Bool
is_given then Char -> SDoc
char Char
'G' else Char -> SDoc
char Char
'W')
instance Outputable EvTerm where
ppr :: EvTerm -> SDoc
ppr (EvExpr EvExpr
e) = EvExpr -> SDoc
forall a. Outputable a => a -> SDoc
ppr EvExpr
e
ppr (EvTypeable TcType
ty EvTypeable
ev) = EvTypeable -> SDoc
forall a. Outputable a => a -> SDoc
ppr EvTypeable
ev SDoc -> SDoc -> SDoc
<+> SDoc
dcolon SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"Typeable" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
ppr TcType
ty
ppr (EvFun { et_tvs :: EvTerm -> [TyVar]
et_tvs = [TyVar]
tvs, et_given :: EvTerm -> [TyVar]
et_given = [TyVar]
gs, et_binds :: EvTerm -> TcEvBinds
et_binds = TcEvBinds
bs, et_body :: EvTerm -> TyVar
et_body = TyVar
w })
= SDoc -> BranchIndex -> SDoc -> SDoc
hang (String -> SDoc
text String
"\\" SDoc -> SDoc -> SDoc
<+> [SDoc] -> SDoc
sep ((TyVar -> SDoc) -> [TyVar] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map TyVar -> SDoc
pprLamBndr ([TyVar]
tvs [TyVar] -> [TyVar] -> [TyVar]
forall a. [a] -> [a] -> [a]
++ [TyVar]
gs)) SDoc -> SDoc -> SDoc
<+> SDoc
arrow)
BranchIndex
2 (TcEvBinds -> SDoc
forall a. Outputable a => a -> SDoc
ppr TcEvBinds
bs SDoc -> SDoc -> SDoc
$$ TyVar -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyVar
w)
instance Outputable EvCallStack where
ppr :: EvCallStack -> SDoc
ppr EvCallStack
EvCsEmpty
= String -> SDoc
text String
"[]"
ppr (EvCsPushCall Name
name RealSrcSpan
loc EvExpr
tm)
= (Name, RealSrcSpan) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Name
name,RealSrcSpan
loc) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
":" SDoc -> SDoc -> SDoc
<+> EvExpr -> SDoc
forall a. Outputable a => a -> SDoc
ppr EvExpr
tm
instance Outputable EvTypeable where
ppr :: EvTypeable -> SDoc
ppr (EvTypeableTyCon TyCon
ts [EvTerm]
_) = String -> SDoc
text String
"TyCon" SDoc -> SDoc -> SDoc
<+> TyCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyCon
ts
ppr (EvTypeableTyApp EvTerm
t1 EvTerm
t2) = SDoc -> SDoc
parens (EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
ppr EvTerm
t1 SDoc -> SDoc -> SDoc
<+> EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
ppr EvTerm
t2)
ppr (EvTypeableTrFun EvTerm
t1 EvTerm
t2) = SDoc -> SDoc
parens (EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
ppr EvTerm
t1 SDoc -> SDoc -> SDoc
<+> SDoc
arrow SDoc -> SDoc -> SDoc
<+> EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
ppr EvTerm
t2)
ppr (EvTypeableTyLit EvTerm
t1) = String -> SDoc
text String
"TyLit" SDoc -> SDoc -> SDoc
<> EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
ppr EvTerm
t1
unwrapIP :: Type -> CoercionR
unwrapIP :: TcType -> TcCoercion
unwrapIP TcType
ty =
case TyCon -> Maybe ([TyVar], TcType, CoAxiom Unbranched)
unwrapNewTyCon_maybe TyCon
tc of
Just ([TyVar]
_,TcType
_,CoAxiom Unbranched
ax) -> Role
-> CoAxiom Unbranched -> [TcType] -> [TcCoercion] -> TcCoercion
mkUnbranchedAxInstCo Role
Representational CoAxiom Unbranched
ax [TcType]
tys []
Maybe ([TyVar], TcType, CoAxiom Unbranched)
Nothing -> String -> SDoc -> TcCoercion
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"unwrapIP" (SDoc -> TcCoercion) -> SDoc -> TcCoercion
forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
"The dictionary for" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (TyCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyCon
tc)
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"is not a newtype!"
where
(TyCon
tc, [TcType]
tys) = TcType -> (TyCon, [TcType])
splitTyConApp TcType
ty
wrapIP :: Type -> CoercionR
wrapIP :: TcType -> TcCoercion
wrapIP TcType
ty = TcCoercion -> TcCoercion
mkSymCo (TcType -> TcCoercion
unwrapIP TcType
ty)