{-# LANGUAGE CPP, DeriveDataTypeable #-}
{-# LANGUAGE LambdaCase #-}
module GHC.Tc.Types.Evidence (
HsWrapper(..),
(<.>), mkWpTyApps, mkWpEvApps, mkWpEvVarApps, mkWpTyLams,
mkWpLams, mkWpLet, mkWpCastN, mkWpCastR, collectHsWrapBinders,
mkWpFun, idHsWrapper, isIdHsWrapper,
pprHsWrapper, hsWrapDictBinders,
TcEvBinds(..), EvBindsVar(..),
EvBindMap(..), emptyEvBindMap, extendEvBinds,
lookupEvBind, evBindMapBinds,
foldEvBindMap, nonDetStrictFoldEvBindMap,
filterEvBindMap,
isEmptyEvBindMap,
evBindMapToVarSet,
varSetMinusEvBindMap,
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,
mkTcCoVarCo,
isTcReflCo, isTcReflexiveCo,
tcCoercionRole,
unwrapIP, wrapIP,
QuoteWrapper(..), applyQuoteWrapper, quoteWrapperTyVarTy
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Types.Unique.DFM
import GHC.Types.Unique.FM
import GHC.Types.Var
import GHC.Core.Coercion.Axiom
import GHC.Core.Coercion
import GHC.Core.Ppr ()
import GHC.Tc.Utils.TcType
import GHC.Core.Type
import GHC.Core.TyCon
import GHC.Core.DataCon( DataCon, dataConWrapId )
import GHC.Core.Class( Class )
import GHC.Builtin.Names
import GHC.Types.Var.Env
import GHC.Types.Var.Set
import GHC.Core.Predicate
import GHC.Types.Name
import GHC.Data.Pair
import GHC.Core
import GHC.Core.Class ( classSCSelId )
import GHC.Core.FVs ( exprSomeFreeVars )
import GHC.Utils.Misc
import GHC.Data.Bag
import qualified Data.Data as Data
import GHC.Utils.Outputable
import GHC.Types.SrcLoc
import Data.IORef( IORef )
import GHC.Types.Unique.Set
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
isTcReflCo :: TcCoercion -> Bool
isTcReflexiveCo :: TcCoercion -> Bool
mkTcReflCo :: Role -> TcType -> TcCoercionR
mkTcReflCo = Role -> TcType -> TcCoercionR
mkReflCo
mkTcSymCo :: TcCoercionR -> TcCoercionR
mkTcSymCo = TcCoercionR -> TcCoercionR
mkSymCo
mkTcTransCo :: TcCoercionR -> TcCoercionR -> TcCoercionR
mkTcTransCo = TcCoercionR -> TcCoercionR -> TcCoercionR
mkTransCo
mkTcNomReflCo :: TcType -> TcCoercionR
mkTcNomReflCo = TcType -> TcCoercionR
mkNomReflCo
mkTcRepReflCo :: TcType -> TcCoercionR
mkTcRepReflCo = TcType -> TcCoercionR
mkRepReflCo
mkTcTyConAppCo :: Role -> TyCon -> [TcCoercionR] -> TcCoercionR
mkTcTyConAppCo = HasDebugCallStack => Role -> TyCon -> [TcCoercionR] -> TcCoercionR
Role -> TyCon -> [TcCoercionR] -> TcCoercionR
External instance of the constraint type HasDebugCallStack
mkTyConAppCo
mkTcAppCo :: TcCoercionR -> TcCoercionR -> TcCoercionR
mkTcAppCo = TcCoercionR -> TcCoercionR -> TcCoercionR
mkAppCo
mkTcFunCo :: Role -> TcCoercionR -> TcCoercionR -> TcCoercionR
mkTcFunCo = Role -> TcCoercionR -> TcCoercionR -> TcCoercionR
mkFunCo
mkTcAxInstCo :: Role
-> CoAxiom br -> Int -> [TcType] -> [TcCoercionR] -> TcCoercionR
mkTcAxInstCo = Role
-> CoAxiom br -> Int -> [TcType] -> [TcCoercionR] -> TcCoercionR
forall (br :: BranchFlag).
Role
-> CoAxiom br -> Int -> [TcType] -> [TcCoercionR] -> TcCoercionR
mkAxInstCo
mkTcUnbranchedAxInstCo :: CoAxiom Unbranched -> [TcType] -> [TcCoercionR] -> TcCoercionR
mkTcUnbranchedAxInstCo = Role
-> CoAxiom Unbranched -> [TcType] -> [TcCoercionR] -> TcCoercionR
mkUnbranchedAxInstCo Role
Representational
mkTcForAllCo :: Id -> TcCoercionR -> TcCoercionR -> TcCoercionR
mkTcForAllCo = Id -> TcCoercionR -> TcCoercionR -> TcCoercionR
mkForAllCo
mkTcForAllCos :: [(Id, TcCoercionR)] -> TcCoercionR -> TcCoercionR
mkTcForAllCos = [(Id, TcCoercionR)] -> TcCoercionR -> TcCoercionR
mkForAllCos
mkTcNthCo :: Role -> Int -> TcCoercionR -> TcCoercionR
mkTcNthCo = HasDebugCallStack => Role -> Int -> TcCoercionR -> TcCoercionR
Role -> Int -> TcCoercionR -> TcCoercionR
External instance of the constraint type HasDebugCallStack
mkNthCo
mkTcLRCo :: LeftOrRight -> TcCoercionR -> TcCoercionR
mkTcLRCo = LeftOrRight -> TcCoercionR -> TcCoercionR
mkLRCo
mkTcSubCo :: TcCoercionR -> TcCoercionR
mkTcSubCo = TcCoercionR -> TcCoercionR
mkSubCo
tcDowngradeRole :: Role -> Role -> TcCoercionR -> TcCoercionR
tcDowngradeRole = Role -> Role -> TcCoercionR -> TcCoercionR
downgradeRole
mkTcAxiomRuleCo :: CoAxiomRule -> [TcCoercionR] -> TcCoercionR
mkTcAxiomRuleCo = CoAxiomRule -> [TcCoercionR] -> TcCoercionR
mkAxiomRuleCo
mkTcGReflRightCo :: Role -> TcType -> TcCoercionR -> TcCoercionR
mkTcGReflRightCo = Role -> TcType -> TcCoercionR -> TcCoercionR
mkGReflRightCo
mkTcGReflLeftCo :: Role -> TcType -> TcCoercionR -> TcCoercionR
mkTcGReflLeftCo = Role -> TcType -> TcCoercionR -> TcCoercionR
mkGReflLeftCo
mkTcCoherenceLeftCo :: Role -> TcType -> TcCoercionR -> TcCoercionR -> TcCoercionR
mkTcCoherenceLeftCo = Role -> TcType -> TcCoercionR -> TcCoercionR -> TcCoercionR
mkCoherenceLeftCo
mkTcCoherenceRightCo :: Role -> TcType -> TcCoercionR -> TcCoercionR -> TcCoercionR
mkTcCoherenceRightCo = Role -> TcType -> TcCoercionR -> TcCoercionR -> TcCoercionR
mkCoherenceRightCo
mkTcPhantomCo :: TcCoercionR -> TcType -> TcType -> TcCoercionR
mkTcPhantomCo = TcCoercionR -> TcType -> TcType -> TcCoercionR
mkPhantomCo
mkTcKindCo :: TcCoercionR -> TcCoercionR
mkTcKindCo = TcCoercionR -> TcCoercionR
mkKindCo
mkTcCoVarCo :: Id -> TcCoercionR
mkTcCoVarCo = Id -> TcCoercionR
mkCoVarCo
tcCoercionKind :: TcCoercionR -> Pair TcType
tcCoercionKind = TcCoercionR -> Pair TcType
coercionKind
tcCoercionRole :: TcCoercionR -> Role
tcCoercionRole = TcCoercionR -> Role
coercionRole
isTcReflCo :: TcCoercionR -> Bool
isTcReflCo = TcCoercionR -> Bool
isReflCo
isTcReflexiveCo :: TcCoercionR -> Bool
isTcReflexiveCo = TcCoercionR -> Bool
isReflexiveCo
maybeTcSubCo :: EqRel -> TcCoercion -> TcCoercion
maybeTcSubCo :: EqRel -> TcCoercionR -> TcCoercionR
maybeTcSubCo EqRel
NomEq = TcCoercionR -> TcCoercionR
forall a. a -> a
id
maybeTcSubCo EqRel
ReprEq = TcCoercionR -> TcCoercionR
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
Instance of class: Data of the constraint type Data HsWrapper
`k` HsWrapper
a1 c (HsWrapper -> HsWrapper) -> HsWrapper -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
Instance of class: Data of the constraint type Data HsWrapper
`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
Instance of class: Data of the constraint type Data HsWrapper
`k` HsWrapper
a1 c (HsWrapper -> TcType -> HsWrapper)
-> HsWrapper -> c (TcType -> HsWrapper)
forall d b. Data d => c (d -> b) -> d -> c b
Instance of class: Data of the constraint type Data HsWrapper
`k` HsWrapper
a2 c (TcType -> HsWrapper) -> TcType -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
External instance of the constraint type Data TcType
`k` TcType
a3
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
k forall g. g -> c g
z (WpCast TcCoercionR
a1) = (TcCoercionR -> HsWrapper) -> c (TcCoercionR -> HsWrapper)
forall g. g -> c g
z TcCoercionR -> HsWrapper
WpCast c (TcCoercionR -> HsWrapper) -> TcCoercionR -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
External instance of the constraint type Data TcCoercionR
`k` TcCoercionR
a1
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
k forall g. g -> c g
z (WpEvLam Id
a1) = (Id -> HsWrapper) -> c (Id -> HsWrapper)
forall g. g -> c g
z Id -> HsWrapper
WpEvLam c (Id -> HsWrapper) -> Id -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
External instance of the constraint type Data Id
`k` Id
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
Instance of class: Data of the constraint type Data EvTerm
`k` EvTerm
a1
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
k forall g. g -> c g
z (WpTyLam Id
a1) = (Id -> HsWrapper) -> c (Id -> HsWrapper)
forall g. g -> c g
z Id -> HsWrapper
WpTyLam c (Id -> HsWrapper) -> Id -> c HsWrapper
forall d b. Data d => c (d -> b) -> d -> c b
External instance of the constraint type Data Id
`k` Id
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
External instance of the constraint type Data TcType
`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
Instance of class: Data of the constraint type Data TcEvBinds
`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 -> Int
Data.constrIndex Constr
c of
Int
1 -> HsWrapper -> c HsWrapper
forall r. r -> c r
z HsWrapper
WpHole
Int
2 -> c (HsWrapper -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
Instance of class: Data of the constraint type Data HsWrapper
k (c (HsWrapper -> HsWrapper -> HsWrapper)
-> c (HsWrapper -> HsWrapper)
forall b r. Data b => c (b -> r) -> c r
Instance of class: Data of the constraint type Data HsWrapper
k ((HsWrapper -> HsWrapper -> HsWrapper)
-> c (HsWrapper -> HsWrapper -> HsWrapper)
forall r. r -> c r
z HsWrapper -> HsWrapper -> HsWrapper
WpCompose))
Int
3 -> c (TcType -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
External instance of the constraint type Data TcType
k (c (HsWrapper -> TcType -> HsWrapper) -> c (TcType -> HsWrapper)
forall b r. Data b => c (b -> r) -> c r
Instance of class: Data of the constraint type Data HsWrapper
k (c (HsWrapper -> HsWrapper -> TcType -> HsWrapper)
-> c (HsWrapper -> TcType -> HsWrapper)
forall b r. Data b => c (b -> r) -> c r
Instance of class: Data of the constraint type Data HsWrapper
k ((HsWrapper -> HsWrapper -> TcType -> HsWrapper)
-> c (HsWrapper -> HsWrapper -> TcType -> HsWrapper)
forall r. r -> c r
z HsWrapper -> HsWrapper -> TcType -> HsWrapper
wpFunEmpty)))
Int
4 -> c (TcCoercionR -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
External instance of the constraint type Data TcCoercionR
k ((TcCoercionR -> HsWrapper) -> c (TcCoercionR -> HsWrapper)
forall r. r -> c r
z TcCoercionR -> HsWrapper
WpCast)
Int
5 -> c (Id -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
External instance of the constraint type Data Id
k ((Id -> HsWrapper) -> c (Id -> HsWrapper)
forall r. r -> c r
z Id -> HsWrapper
WpEvLam)
Int
6 -> c (EvTerm -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
Instance of class: Data of the constraint type Data EvTerm
k ((EvTerm -> HsWrapper) -> c (EvTerm -> HsWrapper)
forall r. r -> c r
z EvTerm -> HsWrapper
WpEvApp)
Int
7 -> c (Id -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
External instance of the constraint type Data Id
k ((Id -> HsWrapper) -> c (Id -> HsWrapper)
forall r. r -> c r
z Id -> HsWrapper
WpTyLam)
Int
8 -> c (TcType -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
External instance of the constraint type Data TcType
k ((TcType -> HsWrapper) -> c (TcType -> HsWrapper)
forall r. r -> c r
z TcType -> HsWrapper
WpTyApp)
Int
_ -> c (TcEvBinds -> HsWrapper) -> c HsWrapper
forall b r. Data b => c (b -> r) -> c r
Instance of class: Data of the constraint type Data TcEvBinds
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 TcCoercionR
_) = Constr
wpCast_constr
toConstr (WpEvLam Id
_) = Constr
wpEvLam_constr
toConstr (WpEvApp EvTerm
_) = Constr
wpEvApp_constr
toConstr (WpTyLam Id
_) = 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 TcCoercionR
co2) TcType
t1 TcType
_ SDoc
_ = TcCoercionR -> HsWrapper
WpCast (Role -> TcCoercionR -> TcCoercionR -> TcCoercionR
mkTcFunCo Role
Representational (TcType -> TcCoercionR
mkTcRepReflCo TcType
t1) TcCoercionR
co2)
mkWpFun (WpCast TcCoercionR
co1) HsWrapper
WpHole TcType
_ TcType
t2 SDoc
_ = TcCoercionR -> HsWrapper
WpCast (Role -> TcCoercionR -> TcCoercionR -> TcCoercionR
mkTcFunCo Role
Representational (TcCoercionR -> TcCoercionR
mkTcSymCo TcCoercionR
co1) (TcType -> TcCoercionR
mkTcRepReflCo TcType
t2))
mkWpFun (WpCast TcCoercionR
co1) (WpCast TcCoercionR
co2) TcType
_ TcType
_ SDoc
_ = TcCoercionR -> HsWrapper
WpCast (Role -> TcCoercionR -> TcCoercionR -> TcCoercionR
mkTcFunCo Role
Representational (TcCoercionR -> TcCoercionR
mkTcSymCo TcCoercionR
co1) TcCoercionR
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 :: TcCoercionR -> HsWrapper
mkWpCastR TcCoercionR
co
| TcCoercionR -> Bool
isTcReflCo TcCoercionR
co = HsWrapper
WpHole
| Bool
otherwise = ASSERT2(tcCoercionRole co == Representational, ppr co)
TcCoercionR -> HsWrapper
WpCast TcCoercionR
co
mkWpCastN :: TcCoercionN -> HsWrapper
mkWpCastN :: TcCoercionR -> HsWrapper
mkWpCastN TcCoercionR
co
| TcCoercionR -> Bool
isTcReflCo TcCoercionR
co = HsWrapper
WpHole
| Bool
otherwise = ASSERT2(tcCoercionRole co == Nominal, ppr co)
TcCoercionR -> HsWrapper
WpCast (TcCoercionR -> TcCoercionR
mkTcSubCo TcCoercionR
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 :: [Id] -> HsWrapper
mkWpEvVarApps [Id]
vs = (EvTerm -> HsWrapper) -> [EvTerm] -> HsWrapper
forall a. (a -> HsWrapper) -> [a] -> HsWrapper
mk_co_app_fn EvTerm -> HsWrapper
WpEvApp ((Id -> EvTerm) -> [Id] -> [EvTerm]
forall a b. (a -> b) -> [a] -> [b]
map (EvExpr -> EvTerm
EvExpr (EvExpr -> EvTerm) -> (Id -> EvExpr) -> Id -> EvTerm
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Id -> EvExpr
evId) [Id]
vs)
mkWpTyLams :: [TyVar] -> HsWrapper
mkWpTyLams :: [Id] -> HsWrapper
mkWpTyLams [Id]
ids = (Id -> HsWrapper) -> [Id] -> HsWrapper
forall a. (a -> HsWrapper) -> [a] -> HsWrapper
mk_co_lam_fn Id -> HsWrapper
WpTyLam [Id]
ids
mkWpLams :: [Var] -> HsWrapper
mkWpLams :: [Id] -> HsWrapper
mkWpLams [Id]
ids = (Id -> HsWrapper) -> [Id] -> HsWrapper
forall a. (a -> HsWrapper) -> [a] -> HsWrapper
mk_co_lam_fn Id -> HsWrapper
WpEvLam [Id]
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
External instance of the constraint type Foldable []
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
External instance of the constraint type Foldable []
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
hsWrapDictBinders :: HsWrapper -> Bag DictId
hsWrapDictBinders :: HsWrapper -> Bag Id
hsWrapDictBinders HsWrapper
wrap = HsWrapper -> Bag Id
go HsWrapper
wrap
where
go :: HsWrapper -> Bag Id
go (WpEvLam Id
dict_id) = Id -> Bag Id
forall a. a -> Bag a
unitBag Id
dict_id
go (HsWrapper
w1 `WpCompose` HsWrapper
w2) = HsWrapper -> Bag Id
go HsWrapper
w1 Bag Id -> Bag Id -> Bag Id
forall a. Bag a -> Bag a -> Bag a
`unionBags` HsWrapper -> Bag Id
go HsWrapper
w2
go (WpFun HsWrapper
_ HsWrapper
w TcType
_ SDoc
_) = HsWrapper -> Bag Id
go HsWrapper
w
go HsWrapper
WpHole = Bag Id
forall a. Bag a
emptyBag
go (WpCast {}) = Bag Id
forall a. Bag a
emptyBag
go (WpEvApp {}) = Bag Id
forall a. Bag a
emptyBag
go (WpTyLam {}) = Bag Id
forall a. Bag a
emptyBag
go (WpTyApp {}) = Bag Id
forall a. Bag a
emptyBag
go (WpLet {}) = Bag Id
forall a. Bag a
emptyBag
collectHsWrapBinders :: HsWrapper -> ([Var], HsWrapper)
collectHsWrapBinders :: HsWrapper -> ([Id], HsWrapper)
collectHsWrapBinders HsWrapper
wrap = HsWrapper -> [HsWrapper] -> ([Id], HsWrapper)
go HsWrapper
wrap []
where
go :: HsWrapper -> [HsWrapper] -> ([Var], HsWrapper)
go :: HsWrapper -> [HsWrapper] -> ([Id], HsWrapper)
go (WpEvLam Id
v) [HsWrapper]
wraps = Id -> ([Id], HsWrapper) -> ([Id], HsWrapper)
forall {a} {b}. a -> ([a], b) -> ([a], b)
add_lam Id
v ([HsWrapper] -> ([Id], HsWrapper)
gos [HsWrapper]
wraps)
go (WpTyLam Id
v) [HsWrapper]
wraps = Id -> ([Id], HsWrapper) -> ([Id], HsWrapper)
forall {a} {b}. a -> ([a], b) -> ([a], b)
add_lam Id
v ([HsWrapper] -> ([Id], HsWrapper)
gos [HsWrapper]
wraps)
go (WpCompose HsWrapper
w1 HsWrapper
w2) [HsWrapper]
wraps = HsWrapper -> [HsWrapper] -> ([Id], 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
External instance of the constraint type Foldable []
foldl' HsWrapper -> HsWrapper -> HsWrapper
(<.>) HsWrapper
wrap [HsWrapper]
wraps)
gos :: [HsWrapper] -> ([Id], HsWrapper)
gos [] = ([], HsWrapper
WpHole)
gos (HsWrapper
w:[HsWrapper]
ws) = HsWrapper -> [HsWrapper] -> ([Id], 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 CoVarSet
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 -> Id -> EvBind -> DVarEnv EvBind
forall a. DVarEnv a -> Id -> a -> DVarEnv a
extendDVarEnv (EvBindMap -> DVarEnv EvBind
ev_bind_varenv EvBindMap
bs)
(EvBind -> Id
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 -> Id -> Maybe EvBind
lookupEvBind EvBindMap
bs = DVarEnv EvBind -> Id -> Maybe EvBind
forall a. DVarEnv a -> Id -> 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)
nonDetStrictFoldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a
nonDetStrictFoldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a
nonDetStrictFoldEvBindMap 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
nonDetStrictFoldDVarEnv 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 }
evBindMapToVarSet :: EvBindMap -> VarSet
evBindMapToVarSet :: EvBindMap -> CoVarSet
evBindMapToVarSet (EvBindMap DVarEnv EvBind
dve) = UniqFM Id -> CoVarSet
forall a. UniqFM a -> UniqSet a
unsafeUFMToUniqSet ((EvBind -> Id) -> UniqFM EvBind -> UniqFM Id
forall elt1 elt2. (elt1 -> elt2) -> UniqFM elt1 -> UniqFM elt2
mapUFM EvBind -> Id
evBindVar (DVarEnv EvBind -> UniqFM EvBind
forall elt. UniqDFM elt -> UniqFM elt
udfmToUfm DVarEnv EvBind
dve))
varSetMinusEvBindMap :: VarSet -> EvBindMap -> VarSet
varSetMinusEvBindMap :: CoVarSet -> EvBindMap -> CoVarSet
varSetMinusEvBindMap CoVarSet
vs (EvBindMap DVarEnv EvBind
dve) = CoVarSet
vs CoVarSet -> DVarEnv EvBind -> CoVarSet
forall a b. UniqSet a -> UniqDFM b -> UniqSet a
`uniqSetMinusUDFM` DVarEnv EvBind
dve
instance Outputable EvBindMap where
ppr :: EvBindMap -> SDoc
ppr (EvBindMap DVarEnv EvBind
m) = DVarEnv EvBind -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable (UniqDFM a)
Instance of class: Outputable of the constraint type Outputable EvBind
ppr DVarEnv EvBind
m
data EvBind
= EvBind { EvBind -> Id
eb_lhs :: EvVar
, EvBind -> EvTerm
eb_rhs :: EvTerm
, EvBind -> Bool
eb_is_given :: Bool
}
evBindVar :: EvBind -> EvVar
evBindVar :: EvBind -> Id
evBindVar = EvBind -> Id
eb_lhs
mkWantedEvBind :: EvVar -> EvTerm -> EvBind
mkWantedEvBind :: Id -> EvTerm -> EvBind
mkWantedEvBind Id
ev EvTerm
tm = EvBind :: Id -> EvTerm -> Bool -> EvBind
EvBind { eb_is_given :: Bool
eb_is_given = Bool
False, eb_lhs :: Id
eb_lhs = Id
ev, eb_rhs :: EvTerm
eb_rhs = EvTerm
tm }
mkGivenEvBind :: EvVar -> EvTerm -> EvBind
mkGivenEvBind :: Id -> EvTerm -> EvBind
mkGivenEvBind Id
ev EvTerm
tm = EvBind :: Id -> EvTerm -> Bool -> EvBind
EvBind { eb_is_given :: Bool
eb_is_given = Bool
True, eb_lhs :: Id
eb_lhs = Id
ev, eb_rhs :: EvTerm
eb_rhs = EvTerm
tm }
data EvTerm
= EvExpr EvExpr
| EvTypeable Type EvTypeable
| EvFun
{ EvTerm -> [Id]
et_tvs :: [TyVar]
, EvTerm -> [Id]
et_given :: [EvVar]
, EvTerm -> TcEvBinds
et_binds :: TcEvBinds
, EvTerm -> Id
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. Int -> (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. Int -> (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. Int -> (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 :: Int -> (forall d. Data d => d -> u) -> EvTerm -> u
$cgmapQi :: forall u. Int -> (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
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Id
External instance of the constraint type Data Id
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Id
External instance of the constraint type Data Id
External instance of the constraint type forall b. Data b => Data (Expr b)
External instance of the constraint type Data Id
External instance of the constraint type Data TcType
Instance of class: Data of the constraint type Data TcEvBinds
Instance of class: Data of the constraint type Data EvTypeable
Data.Data
type EvExpr = CoreExpr
evId :: EvId -> EvExpr
evId :: Id -> EvExpr
evId = Id -> EvExpr
forall b. Id -> Expr b
Var
evCoercion :: TcCoercion -> EvTerm
evCoercion :: TcCoercionR -> EvTerm
evCoercion TcCoercionR
co = EvExpr -> EvTerm
EvExpr (TcCoercionR -> EvExpr
forall b. TcCoercionR -> Expr b
Coercion TcCoercionR
co)
evCast :: EvExpr -> TcCoercion -> EvTerm
evCast :: EvExpr -> TcCoercionR -> EvTerm
evCast EvExpr
et TcCoercionR
tc | TcCoercionR -> Bool
isReflCo TcCoercionR
tc = EvExpr -> EvTerm
EvExpr EvExpr
et
| Bool
otherwise = EvExpr -> EvTerm
EvExpr (EvExpr -> TcCoercionR -> EvExpr
forall b. Expr b -> TcCoercionR -> Expr b
Cast EvExpr
et TcCoercionR
tc)
evDFunApp :: DFunId -> [Type] -> [EvExpr] -> EvTerm
evDFunApp :: Id -> [TcType] -> [EvExpr] -> EvTerm
evDFunApp Id
df [TcType]
tys [EvExpr]
ets = EvExpr -> EvTerm
EvExpr (EvExpr -> EvTerm) -> EvExpr -> EvTerm
forall a b. (a -> b) -> a -> b
$ Id -> EvExpr
forall b. Id -> Expr b
Var Id
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 = Id -> [TcType] -> [EvExpr] -> EvTerm
evDFunApp (DataCon -> Id
dataConWrapId DataCon
dc) [TcType]
tys [EvExpr]
ets
evSelector :: Id -> [Type] -> [EvExpr] -> EvExpr
evSelector :: Id -> [TcType] -> [EvExpr] -> EvExpr
evSelector Id
sel_id [TcType]
tys [EvExpr]
tms = Id -> EvExpr
forall b. Id -> Expr b
Var Id
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.
Int -> (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. Int -> (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. Int -> (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 :: Int -> (forall d. Data d => d -> u) -> EvTypeable -> u
$cgmapQi :: forall u. Int -> (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
Instance of class: Data of the constraint type Data EvTerm
External instance of the constraint type Data TyCon
Instance of class: Data of the constraint type Data EvTerm
External instance of the constraint type forall a. Data a => Data [a]
Instance of class: Data of the constraint type Data EvTerm
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.
Int -> (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. Int -> (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. Int -> (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 :: Int -> (forall d. Data d => d -> u) -> EvCallStack -> u
$cgmapQi :: forall u. Int -> (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
External instance of the constraint type Data Id
External instance of the constraint type Data Name
External instance of the constraint type Data RealSrcSpan
External instance of the constraint type Data Id
External instance of the constraint type forall b. Data b => Data (Expr b)
External instance of the constraint type Data Id
Data.Data
mkEvCast :: EvExpr -> TcCoercion -> EvTerm
mkEvCast :: EvExpr -> TcCoercionR -> EvTerm
mkEvCast EvExpr
ev TcCoercionR
lco
| ASSERT2( tcCoercionRole lco == Representational
, (vcat [text "Coercion of wrong role passed to mkEvCast:", ppr ev, ppr lco]))
TcCoercionR -> Bool
isTcReflCo TcCoercionR
lco = EvExpr -> EvTerm
EvExpr EvExpr
ev
| Bool
otherwise = EvExpr -> TcCoercionR -> EvTerm
evCast EvExpr
ev TcCoercionR
lco
mkEvScSelectors
:: Class -> [TcType]
-> [(TcPredType,
EvExpr)
]
mkEvScSelectors :: Class -> [TcType] -> [(TcType, EvExpr)]
mkEvScSelectors Class
cls [TcType]
tys
= (TcType -> Int -> (TcType, EvExpr))
-> [TcType] -> [Int] -> [(TcType, EvExpr)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith TcType -> Int -> (TcType, EvExpr)
forall {a} {b}. a -> Int -> (a, Expr b)
mk_pr (Class -> [TcType] -> [TcType]
immSuperClasses Class
cls [TcType]
tys) [Int
0..]
where
mk_pr :: a -> Int -> (a, Expr b)
mk_pr a
pred Int
i = (a
pred, Id -> Expr b
forall b. Id -> Expr b
Var Id
sc_sel_id Expr b -> [TcType] -> Expr b
forall b. Expr b -> [TcType] -> Expr b
`mkTyApps` [TcType]
tys)
where
sc_sel_id :: Id
sc_sel_id = Class -> Int -> Id
classSCSelId Class
cls Int
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 TcCoercionR
evTermCoercion_maybe EvTerm
ev_term
| EvExpr EvExpr
e <- EvTerm
ev_term = EvExpr -> Maybe TcCoercionR
go EvExpr
e
| Bool
otherwise = Maybe TcCoercionR
forall a. Maybe a
Nothing
where
go :: EvExpr -> Maybe TcCoercion
go :: EvExpr -> Maybe TcCoercionR
go (Var Id
v) = TcCoercionR -> Maybe TcCoercionR
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Maybe
return (Id -> TcCoercionR
mkCoVarCo Id
v)
go (Coercion TcCoercionR
co) = TcCoercionR -> Maybe TcCoercionR
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Maybe
return TcCoercionR
co
go (Cast EvExpr
tm TcCoercionR
co) = do { TcCoercionR
co' <- EvExpr -> Maybe TcCoercionR
go EvExpr
tm
; TcCoercionR -> Maybe TcCoercionR
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Maybe
return (TcCoercionR -> TcCoercionR -> TcCoercionR
mkCoCast TcCoercionR
co' TcCoercionR
co) }
go EvExpr
_ = Maybe TcCoercionR
forall a. Maybe a
Nothing
evTermCoercion :: EvTerm -> TcCoercion
evTermCoercion :: EvTerm -> TcCoercionR
evTermCoercion EvTerm
tm = case EvTerm -> Maybe TcCoercionR
evTermCoercion_maybe EvTerm
tm of
Just TcCoercionR
co -> TcCoercionR
co
Maybe TcCoercionR
Nothing -> String -> SDoc -> TcCoercionR
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"evTermCoercion" (EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable EvTerm
ppr EvTerm
tm)
findNeededEvVars :: EvBindMap -> VarSet -> VarSet
findNeededEvVars :: EvBindMap -> CoVarSet -> CoVarSet
findNeededEvVars EvBindMap
ev_binds CoVarSet
seeds
= (CoVarSet -> CoVarSet) -> CoVarSet -> CoVarSet
transCloVarSet CoVarSet -> CoVarSet
also_needs CoVarSet
seeds
where
also_needs :: VarSet -> VarSet
also_needs :: CoVarSet -> CoVarSet
also_needs CoVarSet
needs = (Id -> CoVarSet -> CoVarSet) -> CoVarSet -> CoVarSet -> CoVarSet
forall elt a. (elt -> a -> a) -> a -> UniqSet elt -> a
nonDetStrictFoldUniqSet Id -> CoVarSet -> CoVarSet
add CoVarSet
emptyVarSet CoVarSet
needs
add :: Var -> VarSet -> VarSet
add :: Id -> CoVarSet -> CoVarSet
add Id
v CoVarSet
needs
| Just EvBind
ev_bind <- EvBindMap -> Id -> Maybe EvBind
lookupEvBind EvBindMap
ev_binds Id
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 -> CoVarSet
evVarsOfTerm EvTerm
rhs CoVarSet -> CoVarSet -> CoVarSet
`unionVarSet` CoVarSet
needs
| Bool
otherwise
= CoVarSet
needs
evVarsOfTerm :: EvTerm -> VarSet
evVarsOfTerm :: EvTerm -> CoVarSet
evVarsOfTerm (EvExpr EvExpr
e) = InterestingVarFun -> EvExpr -> CoVarSet
exprSomeFreeVars InterestingVarFun
isEvVar EvExpr
e
evVarsOfTerm (EvTypeable TcType
_ EvTypeable
ev) = EvTypeable -> CoVarSet
evVarsOfTypeable EvTypeable
ev
evVarsOfTerm (EvFun {}) = CoVarSet
emptyVarSet
evVarsOfTerms :: [EvTerm] -> VarSet
evVarsOfTerms :: [EvTerm] -> CoVarSet
evVarsOfTerms = (EvTerm -> CoVarSet) -> [EvTerm] -> CoVarSet
forall a. (a -> CoVarSet) -> [a] -> CoVarSet
mapUnionVarSet EvTerm -> CoVarSet
evVarsOfTerm
evVarsOfTypeable :: EvTypeable -> VarSet
evVarsOfTypeable :: EvTypeable -> CoVarSet
evVarsOfTypeable EvTypeable
ev =
case EvTypeable
ev of
EvTypeableTyCon TyCon
_ [EvTerm]
e -> (EvTerm -> CoVarSet) -> [EvTerm] -> CoVarSet
forall a. (a -> CoVarSet) -> [a] -> CoVarSet
mapUnionVarSet EvTerm -> CoVarSet
evVarsOfTerm [EvTerm]
e
EvTypeableTyApp EvTerm
e1 EvTerm
e2 -> [EvTerm] -> CoVarSet
evVarsOfTerms [EvTerm
e1,EvTerm
e2]
EvTypeableTrFun EvTerm
e1 EvTerm
e2 -> [EvTerm] -> CoVarSet
evVarsOfTerms [EvTerm
e1,EvTerm
e2]
EvTypeableTyLit EvTerm
e -> EvTerm -> CoVarSet
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
= (SDocContext -> Bool) -> (Bool -> SDoc) -> SDoc
forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> Bool
sdocPrintTypecheckerElaboration ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \case
Bool
True -> (Bool -> SDoc) -> HsWrapper -> Bool -> SDoc
help Bool -> SDoc
pp_thing_inside HsWrapper
wrap Bool
False
Bool
False -> 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
External instance of the constraint type Outputable TcType
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 TcCoercionR
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, Int -> SDoc -> SDoc
nest Int
2 (String -> SDoc
text String
"|>"
SDoc -> SDoc -> SDoc
<+> TcCoercionR -> SDoc
pprParendCo TcCoercionR
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, Int -> SDoc -> SDoc
nest Int
2 (EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable EvTerm
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 Id
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
<> Id -> SDoc
pprLamBndr Id
id SDoc -> SDoc -> SDoc
<> SDoc
dot, Bool -> SDoc
it Bool
False]
help Bool -> SDoc
it (WpTyLam Id
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
<> Id -> SDoc
pprLamBndr Id
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
Instance of class: Outputable of the constraint type Outputable TcEvBinds
ppr TcEvBinds
binds), Bool -> SDoc
it Bool
False]
pprLamBndr :: Id -> SDoc
pprLamBndr :: Id -> SDoc
pprLamBndr Id
v = BindingSite -> Id -> SDoc
forall a. OutputableBndr a => BindingSite -> a -> SDoc
External instance of the constraint type OutputableBndr Id
pprBndr BindingSite
LambdaBind Id
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
Instance of class: Outputable of the constraint type Outputable EvBindsVar
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
Instance of class: Outputable of the constraint type Outputable EvBind
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
External instance of the constraint type Outputable Unique
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
External instance of the constraint type Outputable Unique
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 -> Id
eb_lhs = Id
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
<+> Id -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Id
ppr Id
v
, Int -> SDoc -> SDoc
nest Int
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
Instance of class: Outputable of the constraint type Outputable EvTerm
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
External instance of the constraint type forall b. OutputableBndr b => Outputable (Expr b)
External instance of the constraint type OutputableBndr Id
ppr EvExpr
e
ppr (EvTypeable TcType
ty EvTypeable
ev) = EvTypeable -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable EvTypeable
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
External instance of the constraint type Outputable TcType
ppr TcType
ty
ppr (EvFun { et_tvs :: EvTerm -> [Id]
et_tvs = [Id]
tvs, et_given :: EvTerm -> [Id]
et_given = [Id]
gs, et_binds :: EvTerm -> TcEvBinds
et_binds = TcEvBinds
bs, et_body :: EvTerm -> Id
et_body = Id
w })
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"\\" SDoc -> SDoc -> SDoc
<+> [SDoc] -> SDoc
sep ((Id -> SDoc) -> [Id] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Id -> SDoc
pprLamBndr ([Id]
tvs [Id] -> [Id] -> [Id]
forall a. [a] -> [a] -> [a]
++ [Id]
gs)) SDoc -> SDoc -> SDoc
<+> SDoc
arrow)
Int
2 (TcEvBinds -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable TcEvBinds
ppr TcEvBinds
bs SDoc -> SDoc -> SDoc
$$ Id -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Id
ppr Id
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
External instance of the constraint type forall a b. (Outputable a, Outputable b) => Outputable (a, b)
External instance of the constraint type Outputable Name
External instance of the constraint type Outputable RealSrcSpan
ppr (Name
name,RealSrcSpan
loc) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
":" SDoc -> SDoc -> SDoc
<+> EvExpr -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall b. OutputableBndr b => Outputable (Expr b)
External instance of the constraint type OutputableBndr Id
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
External instance of the constraint type Outputable TyCon
ppr TyCon
ts
ppr (EvTypeableTyApp EvTerm
t1 EvTerm
t2) = SDoc -> SDoc
parens (EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable EvTerm
ppr EvTerm
t1 SDoc -> SDoc -> SDoc
<+> EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable EvTerm
ppr EvTerm
t2)
ppr (EvTypeableTrFun EvTerm
t1 EvTerm
t2) = SDoc -> SDoc
parens (EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable EvTerm
ppr EvTerm
t1 SDoc -> SDoc -> SDoc
<+> SDoc
arrow SDoc -> SDoc -> SDoc
<+> EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable EvTerm
ppr EvTerm
t2)
ppr (EvTypeableTyLit EvTerm
t1) = String -> SDoc
text String
"TyLit" SDoc -> SDoc -> SDoc
<> EvTerm -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable EvTerm
ppr EvTerm
t1
unwrapIP :: Type -> CoercionR
unwrapIP :: TcType -> TcCoercionR
unwrapIP TcType
ty =
case TyCon -> Maybe ([Id], TcType, CoAxiom Unbranched)
unwrapNewTyCon_maybe TyCon
tc of
Just ([Id]
_,TcType
_,CoAxiom Unbranched
ax) -> Role
-> CoAxiom Unbranched -> [TcType] -> [TcCoercionR] -> TcCoercionR
mkUnbranchedAxInstCo Role
Representational CoAxiom Unbranched
ax [TcType]
tys []
Maybe ([Id], TcType, CoAxiom Unbranched)
Nothing -> String -> SDoc -> TcCoercionR
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"unwrapIP" (SDoc -> TcCoercionR) -> SDoc -> TcCoercionR
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
External instance of the constraint type Outputable TyCon
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 -> TcCoercionR
wrapIP TcType
ty = TcCoercionR -> TcCoercionR
mkSymCo (TcType -> TcCoercionR
unwrapIP TcType
ty)
data QuoteWrapper = QuoteWrapper EvVar Type deriving Typeable QuoteWrapper
DataType
Constr
Typeable QuoteWrapper
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QuoteWrapper -> c QuoteWrapper)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QuoteWrapper)
-> (QuoteWrapper -> Constr)
-> (QuoteWrapper -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c QuoteWrapper))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c QuoteWrapper))
-> ((forall b. Data b => b -> b) -> QuoteWrapper -> QuoteWrapper)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QuoteWrapper -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QuoteWrapper -> r)
-> (forall u. (forall d. Data d => d -> u) -> QuoteWrapper -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> QuoteWrapper -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper)
-> Data QuoteWrapper
QuoteWrapper -> DataType
QuoteWrapper -> Constr
(forall b. Data b => b -> b) -> QuoteWrapper -> QuoteWrapper
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QuoteWrapper -> c QuoteWrapper
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QuoteWrapper
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. Int -> (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. Int -> (forall d. Data d => d -> u) -> QuoteWrapper -> u
forall u. (forall d. Data d => d -> u) -> QuoteWrapper -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QuoteWrapper -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QuoteWrapper -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QuoteWrapper
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QuoteWrapper -> c QuoteWrapper
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c QuoteWrapper)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c QuoteWrapper)
$cQuoteWrapper :: Constr
$tQuoteWrapper :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper
gmapMp :: (forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper
gmapM :: (forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper
gmapQi :: Int -> (forall d. Data d => d -> u) -> QuoteWrapper -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> QuoteWrapper -> u
gmapQ :: (forall d. Data d => d -> u) -> QuoteWrapper -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> QuoteWrapper -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QuoteWrapper -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QuoteWrapper -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QuoteWrapper -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QuoteWrapper -> r
gmapT :: (forall b. Data b => b -> b) -> QuoteWrapper -> QuoteWrapper
$cgmapT :: (forall b. Data b => b -> b) -> QuoteWrapper -> QuoteWrapper
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c QuoteWrapper)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c QuoteWrapper)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c QuoteWrapper)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c QuoteWrapper)
dataTypeOf :: QuoteWrapper -> DataType
$cdataTypeOf :: QuoteWrapper -> DataType
toConstr :: QuoteWrapper -> Constr
$ctoConstr :: QuoteWrapper -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QuoteWrapper
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QuoteWrapper
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QuoteWrapper -> c QuoteWrapper
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QuoteWrapper -> c QuoteWrapper
External instance of the constraint type Data Id
External instance of the constraint type Data TcType
Data.Data
quoteWrapperTyVarTy :: QuoteWrapper -> Type
quoteWrapperTyVarTy :: QuoteWrapper -> TcType
quoteWrapperTyVarTy (QuoteWrapper Id
_ TcType
t) = TcType
t
applyQuoteWrapper :: QuoteWrapper -> HsWrapper
applyQuoteWrapper :: QuoteWrapper -> HsWrapper
applyQuoteWrapper (QuoteWrapper Id
ev_var TcType
m_var)
= [Id] -> HsWrapper
mkWpEvVarApps [Id
ev_var] HsWrapper -> HsWrapper -> HsWrapper
<.> [TcType] -> HsWrapper
mkWpTyApps [TcType
m_var]