{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiWayIf #-}
module TcDerivInfer (inferConstraints, simplifyInstanceContexts) where
#include "HsVersions.h"
import GhcPrelude
import Bag
import BasicTypes
import Class
import DataCon
import ErrUtils
import Inst
import Outputable
import PrelNames
import TcDerivUtils
import TcEnv
import TcGenFunctor
import TcGenGenerics
import TcMType
import TcRnMonad
import TcType
import TyCon
import Type
import TcSimplify
import TcValidity (validDerivPred)
import TcUnify (buildImplicationFor, checkConstraints)
import Unify (tcUnifyTy)
import Util
import Var
import VarSet
import Control.Monad
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Reader (ask)
import Data.List
import Data.Maybe
inferConstraints :: DerivSpecMechanism
-> DerivM ([ThetaOrigin], [TyVar], [TcType])
inferConstraints :: DerivSpecMechanism -> DerivM ([ThetaOrigin], [TyVar], [TcType])
inferConstraints mechanism :: DerivSpecMechanism
mechanism
= do { DerivEnv { denv_tc :: DerivEnv -> TyCon
denv_tc = TyCon
tc
, denv_tc_args :: DerivEnv -> [TcType]
denv_tc_args = [TcType]
tc_args
, denv_cls :: DerivEnv -> Class
denv_cls = Class
main_cls
, denv_cls_tys :: DerivEnv -> [TcType]
denv_cls_tys = [TcType]
cls_tys } <- ReaderT DerivEnv TcRn DerivEnv
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
; Bool
wildcard <- DerivM Bool
isStandaloneWildcardDeriv
; let is_anyclass :: Bool
is_anyclass = DerivSpecMechanism -> Bool
isDerivSpecAnyClass DerivSpecMechanism
mechanism
infer_constraints :: DerivM ([ThetaOrigin], [TyVar], [TcType])
infer_constraints
| Bool
is_anyclass = [TcType] -> DerivM ([ThetaOrigin], [TyVar], [TcType])
inferConstraintsDAC [TcType]
inst_tys
| Bool
otherwise = TcType -> [TcType] -> DerivM ([ThetaOrigin], [TyVar], [TcType])
inferConstraintsDataConArgs TcType
inst_ty [TcType]
inst_tys
inst_ty :: TcType
inst_ty = TyCon -> [TcType] -> TcType
mkTyConApp TyCon
tc [TcType]
tc_args
inst_tys :: [TcType]
inst_tys = [TcType]
cls_tys [TcType] -> [TcType] -> [TcType]
forall a. [a] -> [a] -> [a]
++ [TcType
inst_ty]
cls_tvs :: [TyVar]
cls_tvs = Class -> [TyVar]
classTyVars Class
main_cls
sc_constraints :: [ThetaOrigin]
sc_constraints = ASSERT2( equalLength cls_tvs inst_tys
, ppr main_cls <+> ppr inst_tys )
[ CtOrigin
-> TypeOrKind
-> [TyVar]
-> [TyVar]
-> [TcType]
-> [TcType]
-> ThetaOrigin
mkThetaOrigin (Bool -> CtOrigin
mkDerivOrigin Bool
wildcard)
TypeOrKind
TypeLevel [] [] [] ([TcType] -> ThetaOrigin) -> [TcType] -> ThetaOrigin
forall a b. (a -> b) -> a -> b
$
HasCallStack => TCvSubst -> [TcType] -> [TcType]
TCvSubst -> [TcType] -> [TcType]
substTheta TCvSubst
cls_subst (Class -> [TcType]
classSCTheta Class
main_cls) ]
cls_subst :: TCvSubst
cls_subst = ASSERT( equalLength cls_tvs inst_tys )
[TyVar] -> [TcType] -> TCvSubst
HasDebugCallStack => [TyVar] -> [TcType] -> TCvSubst
zipTvSubst [TyVar]
cls_tvs [TcType]
inst_tys
; (inferred_constraints :: [ThetaOrigin]
inferred_constraints, tvs' :: [TyVar]
tvs', inst_tys' :: [TcType]
inst_tys') <- DerivM ([ThetaOrigin], [TyVar], [TcType])
infer_constraints
; IOEnv (Env TcGblEnv TcLclEnv) () -> ReaderT DerivEnv TcRn ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IOEnv (Env TcGblEnv TcLclEnv) () -> ReaderT DerivEnv TcRn ())
-> IOEnv (Env TcGblEnv TcLclEnv) () -> ReaderT DerivEnv TcRn ()
forall a b. (a -> b) -> a -> b
$ String -> SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ()
traceTc "inferConstraints" (SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ())
-> SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ()
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat
[ Class -> SDoc
forall a. Outputable a => a -> SDoc
ppr Class
main_cls SDoc -> SDoc -> SDoc
<+> [TcType] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [TcType]
inst_tys'
, [ThetaOrigin] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [ThetaOrigin]
inferred_constraints
]
; ([ThetaOrigin], [TyVar], [TcType])
-> DerivM ([ThetaOrigin], [TyVar], [TcType])
forall (m :: * -> *) a. Monad m => a -> m a
return ( [ThetaOrigin]
sc_constraints [ThetaOrigin] -> [ThetaOrigin] -> [ThetaOrigin]
forall a. [a] -> [a] -> [a]
++ [ThetaOrigin]
inferred_constraints
, [TyVar]
tvs', [TcType]
inst_tys' ) }
inferConstraintsDataConArgs :: TcType -> [TcType]
-> DerivM ([ThetaOrigin], [TyVar], [TcType])
inferConstraintsDataConArgs :: TcType -> [TcType] -> DerivM ([ThetaOrigin], [TyVar], [TcType])
inferConstraintsDataConArgs inst_ty :: TcType
inst_ty inst_tys :: [TcType]
inst_tys
= do DerivEnv { denv_tvs :: DerivEnv -> [TyVar]
denv_tvs = [TyVar]
tvs
, denv_rep_tc :: DerivEnv -> TyCon
denv_rep_tc = TyCon
rep_tc
, denv_rep_tc_args :: DerivEnv -> [TcType]
denv_rep_tc_args = [TcType]
rep_tc_args
, denv_cls :: DerivEnv -> Class
denv_cls = Class
main_cls
, denv_cls_tys :: DerivEnv -> [TcType]
denv_cls_tys = [TcType]
cls_tys } <- ReaderT DerivEnv TcRn DerivEnv
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
Bool
wildcard <- DerivM Bool
isStandaloneWildcardDeriv
let tc_binders :: [TyConBinder]
tc_binders = TyCon -> [TyConBinder]
tyConBinders TyCon
rep_tc
choose_level :: TyConBinder -> TypeOrKind
choose_level bndr :: TyConBinder
bndr
| TyConBinder -> Bool
isNamedTyConBinder TyConBinder
bndr = TypeOrKind
KindLevel
| Bool
otherwise = TypeOrKind
TypeLevel
t_or_ks :: [TypeOrKind]
t_or_ks = (TyConBinder -> TypeOrKind) -> [TyConBinder] -> [TypeOrKind]
forall a b. (a -> b) -> [a] -> [b]
map TyConBinder -> TypeOrKind
choose_level [TyConBinder]
tc_binders [TypeOrKind] -> [TypeOrKind] -> [TypeOrKind]
forall a. [a] -> [a] -> [a]
++ TypeOrKind -> [TypeOrKind]
forall a. a -> [a]
repeat TypeOrKind
TypeLevel
con_arg_constraints
:: (CtOrigin -> TypeOrKind
-> Type
-> [([PredOrigin], Maybe TCvSubst)])
-> ([ThetaOrigin], [TyVar], [TcType])
con_arg_constraints :: (CtOrigin
-> TypeOrKind -> TcType -> [([PredOrigin], Maybe TCvSubst)])
-> ([ThetaOrigin], [TyVar], [TcType])
con_arg_constraints get_arg_constraints :: CtOrigin
-> TypeOrKind -> TcType -> [([PredOrigin], Maybe TCvSubst)]
get_arg_constraints
= let (predss :: [[PredOrigin]]
predss, mbSubsts :: [Maybe TCvSubst]
mbSubsts) = [([PredOrigin], Maybe TCvSubst)]
-> ([[PredOrigin]], [Maybe TCvSubst])
forall a b. [(a, b)] -> ([a], [b])
unzip
[ ([PredOrigin], Maybe TCvSubst)
preds_and_mbSubst
| DataCon
data_con <- TyCon -> [DataCon]
tyConDataCons TyCon
rep_tc
, (arg_n :: Int
arg_n, arg_t_or_k :: TypeOrKind
arg_t_or_k, arg_ty :: TcType
arg_ty)
<- [Int] -> [TypeOrKind] -> [TcType] -> [(Int, TypeOrKind, TcType)]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [1..] [TypeOrKind]
t_or_ks ([TcType] -> [(Int, TypeOrKind, TcType)])
-> [TcType] -> [(Int, TypeOrKind, TcType)]
forall a b. (a -> b) -> a -> b
$
DataCon -> [TcType] -> [TcType]
dataConInstOrigArgTys DataCon
data_con [TcType]
all_rep_tc_args
, Bool -> Bool
not (HasDebugCallStack => TcType -> Bool
TcType -> Bool
isUnliftedType TcType
arg_ty)
, let orig :: CtOrigin
orig = DataCon -> Int -> Bool -> CtOrigin
DerivOriginDC DataCon
data_con Int
arg_n Bool
wildcard
, ([PredOrigin], Maybe TCvSubst)
preds_and_mbSubst
<- CtOrigin
-> TypeOrKind -> TcType -> [([PredOrigin], Maybe TCvSubst)]
get_arg_constraints CtOrigin
orig TypeOrKind
arg_t_or_k TcType
arg_ty
]
preds :: [PredOrigin]
preds = [[PredOrigin]] -> [PredOrigin]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[PredOrigin]]
predss
subst :: TCvSubst
subst = (TCvSubst -> TCvSubst -> TCvSubst)
-> TCvSubst -> [TCvSubst] -> TCvSubst
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' TCvSubst -> TCvSubst -> TCvSubst
composeTCvSubst
TCvSubst
emptyTCvSubst ([Maybe TCvSubst] -> [TCvSubst]
forall a. [Maybe a] -> [a]
catMaybes [Maybe TCvSubst]
mbSubsts)
unmapped_tvs :: [TyVar]
unmapped_tvs = (TyVar -> Bool) -> [TyVar] -> [TyVar]
forall a. (a -> Bool) -> [a] -> [a]
filter (\v :: TyVar
v -> TyVar
v TyVar -> TCvSubst -> Bool
`notElemTCvSubst` TCvSubst
subst
Bool -> Bool -> Bool
&& Bool -> Bool
not (TyVar
v TyVar -> TCvSubst -> Bool
`isInScope` TCvSubst
subst)) [TyVar]
tvs
(subst' :: TCvSubst
subst', _) = HasCallStack => TCvSubst -> [TyVar] -> (TCvSubst, [TyVar])
TCvSubst -> [TyVar] -> (TCvSubst, [TyVar])
substTyVarBndrs TCvSubst
subst [TyVar]
unmapped_tvs
preds' :: [PredOrigin]
preds' = (PredOrigin -> PredOrigin) -> [PredOrigin] -> [PredOrigin]
forall a b. (a -> b) -> [a] -> [b]
map (HasCallStack => TCvSubst -> PredOrigin -> PredOrigin
TCvSubst -> PredOrigin -> PredOrigin
substPredOrigin TCvSubst
subst') [PredOrigin]
preds
inst_tys' :: [TcType]
inst_tys' = HasCallStack => TCvSubst -> [TcType] -> [TcType]
TCvSubst -> [TcType] -> [TcType]
substTys TCvSubst
subst' [TcType]
inst_tys
tvs' :: [TyVar]
tvs' = [TcType] -> [TyVar]
tyCoVarsOfTypesWellScoped [TcType]
inst_tys'
in ([[PredOrigin] -> ThetaOrigin
mkThetaOriginFromPreds [PredOrigin]
preds'], [TyVar]
tvs', [TcType]
inst_tys')
is_generic :: Bool
is_generic = Class
main_cls Class -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
`hasKey` Unique
genClassKey
is_generic1 :: Bool
is_generic1 = Class
main_cls Class -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
`hasKey` Unique
gen1ClassKey
is_functor_like :: Bool
is_functor_like = HasDebugCallStack => TcType -> TcType
TcType -> TcType
tcTypeKind TcType
inst_ty HasDebugCallStack => TcType -> TcType -> Bool
TcType -> TcType -> Bool
`tcEqKind` TcType
typeToTypeKind
Bool -> Bool -> Bool
|| Bool
is_generic1
get_gen1_constraints :: Class -> CtOrigin -> TypeOrKind -> Type
-> [([PredOrigin], Maybe TCvSubst)]
get_gen1_constraints :: Class
-> CtOrigin
-> TypeOrKind
-> TcType
-> [([PredOrigin], Maybe TCvSubst)]
get_gen1_constraints functor_cls :: Class
functor_cls orig :: CtOrigin
orig t_or_k :: TypeOrKind
t_or_k ty :: TcType
ty
= CtOrigin
-> TypeOrKind
-> Class
-> [TcType]
-> [([PredOrigin], Maybe TCvSubst)]
mk_functor_like_constraints CtOrigin
orig TypeOrKind
t_or_k Class
functor_cls ([TcType] -> [([PredOrigin], Maybe TCvSubst)])
-> [TcType] -> [([PredOrigin], Maybe TCvSubst)]
forall a b. (a -> b) -> a -> b
$
TyVar -> TcType -> [TcType]
get_gen1_constrained_tys TyVar
last_tv TcType
ty
get_std_constrained_tys :: CtOrigin -> TypeOrKind -> Type
-> [([PredOrigin], Maybe TCvSubst)]
get_std_constrained_tys :: CtOrigin
-> TypeOrKind -> TcType -> [([PredOrigin], Maybe TCvSubst)]
get_std_constrained_tys orig :: CtOrigin
orig t_or_k :: TypeOrKind
t_or_k ty :: TcType
ty
| Bool
is_functor_like
= CtOrigin
-> TypeOrKind
-> Class
-> [TcType]
-> [([PredOrigin], Maybe TCvSubst)]
mk_functor_like_constraints CtOrigin
orig TypeOrKind
t_or_k Class
main_cls ([TcType] -> [([PredOrigin], Maybe TCvSubst)])
-> [TcType] -> [([PredOrigin], Maybe TCvSubst)]
forall a b. (a -> b) -> a -> b
$
TyVar -> TcType -> [TcType]
deepSubtypesContaining TyVar
last_tv TcType
ty
| Bool
otherwise
= [( [CtOrigin -> TypeOrKind -> Class -> TcType -> PredOrigin
mk_cls_pred CtOrigin
orig TypeOrKind
t_or_k Class
main_cls TcType
ty]
, Maybe TCvSubst
forall a. Maybe a
Nothing )]
mk_functor_like_constraints :: CtOrigin -> TypeOrKind
-> Class -> [Type]
-> [([PredOrigin], Maybe TCvSubst)]
mk_functor_like_constraints :: CtOrigin
-> TypeOrKind
-> Class
-> [TcType]
-> [([PredOrigin], Maybe TCvSubst)]
mk_functor_like_constraints orig :: CtOrigin
orig t_or_k :: TypeOrKind
t_or_k cls :: Class
cls
= (TcType -> ([PredOrigin], Maybe TCvSubst))
-> [TcType] -> [([PredOrigin], Maybe TCvSubst)]
forall a b. (a -> b) -> [a] -> [b]
map ((TcType -> ([PredOrigin], Maybe TCvSubst))
-> [TcType] -> [([PredOrigin], Maybe TCvSubst)])
-> (TcType -> ([PredOrigin], Maybe TCvSubst))
-> [TcType]
-> [([PredOrigin], Maybe TCvSubst)]
forall a b. (a -> b) -> a -> b
$ \ty :: TcType
ty -> let ki :: TcType
ki = HasDebugCallStack => TcType -> TcType
TcType -> TcType
tcTypeKind TcType
ty in
( [ CtOrigin -> TypeOrKind -> Class -> TcType -> PredOrigin
mk_cls_pred CtOrigin
orig TypeOrKind
t_or_k Class
cls TcType
ty
, CtOrigin -> TypeOrKind -> TcType -> PredOrigin
mkPredOrigin CtOrigin
orig TypeOrKind
KindLevel
(TcType -> TcType -> TcType
mkPrimEqPred TcType
ki TcType
typeToTypeKind) ]
, TcType -> TcType -> Maybe TCvSubst
tcUnifyTy TcType
ki TcType
typeToTypeKind
)
rep_tc_tvs :: [TyVar]
rep_tc_tvs = TyCon -> [TyVar]
tyConTyVars TyCon
rep_tc
last_tv :: TyVar
last_tv = [TyVar] -> TyVar
forall a. [a] -> a
last [TyVar]
rep_tc_tvs
all_rep_tc_args :: [TcType]
all_rep_tc_args
= [TcType]
rep_tc_args [TcType] -> [TcType] -> [TcType]
forall a. [a] -> [a] -> [a]
++ (TyVar -> TcType) -> [TyVar] -> [TcType]
forall a b. (a -> b) -> [a] -> [b]
map TyVar -> TcType
mkTyVarTy
(Int -> [TyVar] -> [TyVar]
forall a. Int -> [a] -> [a]
drop ([TcType] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [TcType]
rep_tc_args) [TyVar]
rep_tc_tvs)
stupid_constraints :: [ThetaOrigin]
stupid_constraints
= [ CtOrigin
-> TypeOrKind
-> [TyVar]
-> [TyVar]
-> [TcType]
-> [TcType]
-> ThetaOrigin
mkThetaOrigin CtOrigin
deriv_origin TypeOrKind
TypeLevel [] [] [] ([TcType] -> ThetaOrigin) -> [TcType] -> ThetaOrigin
forall a b. (a -> b) -> a -> b
$
HasCallStack => TCvSubst -> [TcType] -> [TcType]
TCvSubst -> [TcType] -> [TcType]
substTheta TCvSubst
tc_subst (TyCon -> [TcType]
tyConStupidTheta TyCon
rep_tc) ]
tc_subst :: TCvSubst
tc_subst =
ASSERT( equalLength rep_tc_tvs all_rep_tc_args )
[TyVar] -> [TcType] -> TCvSubst
HasDebugCallStack => [TyVar] -> [TcType] -> TCvSubst
zipTvSubst [TyVar]
rep_tc_tvs [TcType]
all_rep_tc_args
extra_constraints :: [ThetaOrigin]
extra_constraints = [[PredOrigin] -> ThetaOrigin
mkThetaOriginFromPreds [PredOrigin]
constrs]
where
constrs :: [PredOrigin]
constrs
| Class
main_cls Class -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
`hasKey` Unique
dataClassKey
, (TcType -> Bool) -> [TcType] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (TcType -> Bool
isLiftedTypeKind (TcType -> Bool) -> (TcType -> TcType) -> TcType -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasDebugCallStack => TcType -> TcType
TcType -> TcType
tcTypeKind) [TcType]
rep_tc_args
= [ CtOrigin -> TypeOrKind -> Class -> TcType -> PredOrigin
mk_cls_pred CtOrigin
deriv_origin TypeOrKind
t_or_k Class
main_cls TcType
ty
| (t_or_k :: TypeOrKind
t_or_k, ty :: TcType
ty) <- [TypeOrKind] -> [TcType] -> [(TypeOrKind, TcType)]
forall a b. [a] -> [b] -> [(a, b)]
zip [TypeOrKind]
t_or_ks [TcType]
rep_tc_args]
| Bool
otherwise
= []
mk_cls_pred :: CtOrigin -> TypeOrKind -> Class -> TcType -> PredOrigin
mk_cls_pred orig :: CtOrigin
orig t_or_k :: TypeOrKind
t_or_k cls :: Class
cls ty :: TcType
ty
= CtOrigin -> TypeOrKind -> TcType -> PredOrigin
mkPredOrigin CtOrigin
orig TypeOrKind
t_or_k (Class -> [TcType] -> TcType
mkClassPred Class
cls ([TcType]
cls_tys' [TcType] -> [TcType] -> [TcType]
forall a. [a] -> [a] -> [a]
++ [TcType
ty]))
cls_tys' :: [TcType]
cls_tys' | Bool
is_generic1 = []
| Bool
otherwise = [TcType]
cls_tys
deriv_origin :: CtOrigin
deriv_origin = Bool -> CtOrigin
mkDerivOrigin Bool
wildcard
if
| Bool
is_generic
-> ([ThetaOrigin], [TyVar], [TcType])
-> DerivM ([ThetaOrigin], [TyVar], [TcType])
forall (m :: * -> *) a. Monad m => a -> m a
return ([], [TyVar]
tvs, [TcType]
inst_tys)
| Bool
is_generic1
-> ASSERT( rep_tc_tvs `lengthExceeds` 0 )
ASSERT( cls_tys `lengthIs` 1 )
do { Class
functorClass <- IOEnv (Env TcGblEnv TcLclEnv) Class -> ReaderT DerivEnv TcRn Class
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IOEnv (Env TcGblEnv TcLclEnv) Class
-> ReaderT DerivEnv TcRn Class)
-> IOEnv (Env TcGblEnv TcLclEnv) Class
-> ReaderT DerivEnv TcRn Class
forall a b. (a -> b) -> a -> b
$ Name -> IOEnv (Env TcGblEnv TcLclEnv) Class
tcLookupClass Name
functorClassName
; ([ThetaOrigin], [TyVar], [TcType])
-> DerivM ([ThetaOrigin], [TyVar], [TcType])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (([ThetaOrigin], [TyVar], [TcType])
-> DerivM ([ThetaOrigin], [TyVar], [TcType]))
-> ([ThetaOrigin], [TyVar], [TcType])
-> DerivM ([ThetaOrigin], [TyVar], [TcType])
forall a b. (a -> b) -> a -> b
$ (CtOrigin
-> TypeOrKind -> TcType -> [([PredOrigin], Maybe TCvSubst)])
-> ([ThetaOrigin], [TyVar], [TcType])
con_arg_constraints
((CtOrigin
-> TypeOrKind -> TcType -> [([PredOrigin], Maybe TCvSubst)])
-> ([ThetaOrigin], [TyVar], [TcType]))
-> (CtOrigin
-> TypeOrKind -> TcType -> [([PredOrigin], Maybe TCvSubst)])
-> ([ThetaOrigin], [TyVar], [TcType])
forall a b. (a -> b) -> a -> b
$ Class
-> CtOrigin
-> TypeOrKind
-> TcType
-> [([PredOrigin], Maybe TCvSubst)]
get_gen1_constraints Class
functorClass }
| Bool
otherwise
->
ASSERT2( equalLength rep_tc_tvs all_rep_tc_args
, ppr main_cls <+> ppr rep_tc
$$ ppr rep_tc_tvs $$ ppr all_rep_tc_args )
do { let (arg_constraints :: [ThetaOrigin]
arg_constraints, tvs' :: [TyVar]
tvs', inst_tys' :: [TcType]
inst_tys')
= (CtOrigin
-> TypeOrKind -> TcType -> [([PredOrigin], Maybe TCvSubst)])
-> ([ThetaOrigin], [TyVar], [TcType])
con_arg_constraints CtOrigin
-> TypeOrKind -> TcType -> [([PredOrigin], Maybe TCvSubst)]
get_std_constrained_tys
; IOEnv (Env TcGblEnv TcLclEnv) () -> ReaderT DerivEnv TcRn ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IOEnv (Env TcGblEnv TcLclEnv) () -> ReaderT DerivEnv TcRn ())
-> IOEnv (Env TcGblEnv TcLclEnv) () -> ReaderT DerivEnv TcRn ()
forall a b. (a -> b) -> a -> b
$ String -> SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ()
traceTc "inferConstraintsDataConArgs" (SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ())
-> SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ()
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat
[ Class -> SDoc
forall a. Outputable a => a -> SDoc
ppr Class
main_cls SDoc -> SDoc -> SDoc
<+> [TcType] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [TcType]
inst_tys'
, [ThetaOrigin] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [ThetaOrigin]
arg_constraints
]
; ([ThetaOrigin], [TyVar], [TcType])
-> DerivM ([ThetaOrigin], [TyVar], [TcType])
forall (m :: * -> *) a. Monad m => a -> m a
return ( [ThetaOrigin]
stupid_constraints [ThetaOrigin] -> [ThetaOrigin] -> [ThetaOrigin]
forall a. [a] -> [a] -> [a]
++ [ThetaOrigin]
extra_constraints
[ThetaOrigin] -> [ThetaOrigin] -> [ThetaOrigin]
forall a. [a] -> [a] -> [a]
++ [ThetaOrigin]
arg_constraints
, [TyVar]
tvs', [TcType]
inst_tys') }
typeToTypeKind :: Kind
typeToTypeKind :: TcType
typeToTypeKind = TcType
liftedTypeKind TcType -> TcType -> TcType
`mkFunTy` TcType
liftedTypeKind
inferConstraintsDAC :: [TcType] -> DerivM ([ThetaOrigin], [TyVar], [TcType])
inferConstraintsDAC :: [TcType] -> DerivM ([ThetaOrigin], [TyVar], [TcType])
inferConstraintsDAC inst_tys :: [TcType]
inst_tys
= do { DerivEnv { denv_tvs :: DerivEnv -> [TyVar]
denv_tvs = [TyVar]
tvs
, denv_cls :: DerivEnv -> Class
denv_cls = Class
cls } <- ReaderT DerivEnv TcRn DerivEnv
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
; Bool
wildcard <- DerivM Bool
isStandaloneWildcardDeriv
; let gen_dms :: [(TyVar, TcType)]
gen_dms = [ (TyVar
sel_id, TcType
dm_ty)
| (sel_id :: TyVar
sel_id, Just (_, GenericDM dm_ty :: TcType
dm_ty)) <- Class -> [(TyVar, DefMethInfo)]
classOpItems Class
cls ]
cls_tvs :: [TyVar]
cls_tvs = Class -> [TyVar]
classTyVars Class
cls
do_one_meth :: (Id, Type) -> TcM ThetaOrigin
do_one_meth :: (TyVar, TcType) -> TcM ThetaOrigin
do_one_meth (sel_id :: TyVar
sel_id, gen_dm_ty :: TcType
gen_dm_ty)
= do { let (sel_tvs :: [TyVar]
sel_tvs, _cls_pred :: TcType
_cls_pred, meth_ty :: TcType
meth_ty)
= TcType -> ([TyVar], TcType, TcType)
tcSplitMethodTy (TyVar -> TcType
varType TyVar
sel_id)
meth_ty' :: TcType
meth_ty' = HasCallStack => [TyVar] -> [TcType] -> TcType -> TcType
[TyVar] -> [TcType] -> TcType -> TcType
substTyWith [TyVar]
sel_tvs [TcType]
inst_tys TcType
meth_ty
(meth_tvs :: [TyVar]
meth_tvs, meth_theta :: [TcType]
meth_theta, meth_tau :: TcType
meth_tau)
= TcType -> ([TyVar], [TcType], TcType)
tcSplitNestedSigmaTys TcType
meth_ty'
gen_dm_ty' :: TcType
gen_dm_ty' = HasCallStack => [TyVar] -> [TcType] -> TcType -> TcType
[TyVar] -> [TcType] -> TcType -> TcType
substTyWith [TyVar]
cls_tvs [TcType]
inst_tys TcType
gen_dm_ty
(dm_tvs :: [TyVar]
dm_tvs, dm_theta :: [TcType]
dm_theta, dm_tau :: TcType
dm_tau)
= TcType -> ([TyVar], [TcType], TcType)
tcSplitNestedSigmaTys TcType
gen_dm_ty'
tau_eq :: TcType
tau_eq = TcType -> TcType -> TcType
mkPrimEqPred TcType
meth_tau TcType
dm_tau
; ThetaOrigin -> TcM ThetaOrigin
forall (m :: * -> *) a. Monad m => a -> m a
return (CtOrigin
-> TypeOrKind
-> [TyVar]
-> [TyVar]
-> [TcType]
-> [TcType]
-> ThetaOrigin
mkThetaOrigin (Bool -> CtOrigin
mkDerivOrigin Bool
wildcard) TypeOrKind
TypeLevel
[TyVar]
meth_tvs [TyVar]
dm_tvs [TcType]
meth_theta (TcType
tau_eqTcType -> [TcType] -> [TcType]
forall a. a -> [a] -> [a]
:[TcType]
dm_theta)) }
; [ThetaOrigin]
theta_origins <- IOEnv (Env TcGblEnv TcLclEnv) [ThetaOrigin]
-> ReaderT DerivEnv TcRn [ThetaOrigin]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IOEnv (Env TcGblEnv TcLclEnv) [ThetaOrigin]
-> ReaderT DerivEnv TcRn [ThetaOrigin])
-> IOEnv (Env TcGblEnv TcLclEnv) [ThetaOrigin]
-> ReaderT DerivEnv TcRn [ThetaOrigin]
forall a b. (a -> b) -> a -> b
$ ((TyVar, TcType) -> TcM ThetaOrigin)
-> [(TyVar, TcType)] -> IOEnv (Env TcGblEnv TcLclEnv) [ThetaOrigin]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (TyVar, TcType) -> TcM ThetaOrigin
do_one_meth [(TyVar, TcType)]
gen_dms
; ([ThetaOrigin], [TyVar], [TcType])
-> DerivM ([ThetaOrigin], [TyVar], [TcType])
forall (m :: * -> *) a. Monad m => a -> m a
return ([ThetaOrigin]
theta_origins, [TyVar]
tvs, [TcType]
inst_tys) }
simplifyInstanceContexts :: [DerivSpec [ThetaOrigin]]
-> TcM [DerivSpec ThetaType]
simplifyInstanceContexts :: [DerivSpec [ThetaOrigin]] -> TcM [DerivSpec [TcType]]
simplifyInstanceContexts [] = [DerivSpec [TcType]] -> TcM [DerivSpec [TcType]]
forall (m :: * -> *) a. Monad m => a -> m a
return []
simplifyInstanceContexts infer_specs :: [DerivSpec [ThetaOrigin]]
infer_specs
= do { String -> SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ()
traceTc "simplifyInstanceContexts" (SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ())
-> SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ()
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat ((DerivSpec [ThetaOrigin] -> SDoc)
-> [DerivSpec [ThetaOrigin]] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map DerivSpec [ThetaOrigin] -> SDoc
forall theta. Outputable theta => DerivSpec theta -> SDoc
pprDerivSpec [DerivSpec [ThetaOrigin]]
infer_specs)
; Int -> [[TcType]] -> TcM [DerivSpec [TcType]]
iterate_deriv 1 [[TcType]]
initial_solutions }
where
initial_solutions :: [ThetaType]
initial_solutions :: [[TcType]]
initial_solutions = [ [] | DerivSpec [ThetaOrigin]
_ <- [DerivSpec [ThetaOrigin]]
infer_specs ]
iterate_deriv :: Int -> [ThetaType] -> TcM [DerivSpec ThetaType]
iterate_deriv :: Int -> [[TcType]] -> TcM [DerivSpec [TcType]]
iterate_deriv n :: Int
n current_solns :: [[TcType]]
current_solns
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 20
= String -> SDoc -> TcM [DerivSpec [TcType]]
forall a. HasCallStack => String -> SDoc -> a
pprPanic "solveDerivEqns: probable loop"
([SDoc] -> SDoc
vcat ((DerivSpec [ThetaOrigin] -> SDoc)
-> [DerivSpec [ThetaOrigin]] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map DerivSpec [ThetaOrigin] -> SDoc
forall theta. Outputable theta => DerivSpec theta -> SDoc
pprDerivSpec [DerivSpec [ThetaOrigin]]
infer_specs) SDoc -> SDoc -> SDoc
$$ [[TcType]] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [[TcType]]
current_solns)
| Bool
otherwise
= do {
[ClsInst]
inst_specs <- ([TcType]
-> DerivSpec [ThetaOrigin]
-> IOEnv (Env TcGblEnv TcLclEnv) ClsInst)
-> [[TcType]]
-> [DerivSpec [ThetaOrigin]]
-> IOEnv (Env TcGblEnv TcLclEnv) [ClsInst]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM [TcType]
-> DerivSpec [ThetaOrigin] -> IOEnv (Env TcGblEnv TcLclEnv) ClsInst
forall theta.
[TcType]
-> DerivSpec theta -> IOEnv (Env TcGblEnv TcLclEnv) ClsInst
newDerivClsInst [[TcType]]
current_solns [DerivSpec [ThetaOrigin]]
infer_specs
; [[TcType]]
new_solns <- TcM [[TcType]] -> TcM [[TcType]]
forall r. TcM r -> TcM r
checkNoErrs (TcM [[TcType]] -> TcM [[TcType]])
-> TcM [[TcType]] -> TcM [[TcType]]
forall a b. (a -> b) -> a -> b
$
[ClsInst] -> TcM [[TcType]] -> TcM [[TcType]]
forall a. [ClsInst] -> TcM a -> TcM a
extendLocalInstEnv [ClsInst]
inst_specs (TcM [[TcType]] -> TcM [[TcType]])
-> TcM [[TcType]] -> TcM [[TcType]]
forall a b. (a -> b) -> a -> b
$
(DerivSpec [ThetaOrigin] -> IOEnv (Env TcGblEnv TcLclEnv) [TcType])
-> [DerivSpec [ThetaOrigin]] -> TcM [[TcType]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM DerivSpec [ThetaOrigin] -> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
gen_soln [DerivSpec [ThetaOrigin]]
infer_specs
; if ([[TcType]]
current_solns [[TcType]] -> [[TcType]] -> Bool
`eqSolution` [[TcType]]
new_solns) then
[DerivSpec [TcType]] -> TcM [DerivSpec [TcType]]
forall (m :: * -> *) a. Monad m => a -> m a
return [ DerivSpec [ThetaOrigin]
spec { ds_theta :: [TcType]
ds_theta = [TcType]
soln }
| (spec :: DerivSpec [ThetaOrigin]
spec, soln :: [TcType]
soln) <- [DerivSpec [ThetaOrigin]]
-> [[TcType]] -> [(DerivSpec [ThetaOrigin], [TcType])]
forall a b. [a] -> [b] -> [(a, b)]
zip [DerivSpec [ThetaOrigin]]
infer_specs [[TcType]]
current_solns ]
else
Int -> [[TcType]] -> TcM [DerivSpec [TcType]]
iterate_deriv (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+1) [[TcType]]
new_solns }
eqSolution :: [[TcType]] -> [[TcType]] -> Bool
eqSolution a :: [[TcType]]
a b :: [[TcType]]
b = ([TcType] -> [TcType] -> Bool) -> [[TcType]] -> [[TcType]] -> Bool
forall a. (a -> a -> Bool) -> [a] -> [a] -> Bool
eqListBy ((TcType -> TcType -> Bool) -> [TcType] -> [TcType] -> Bool
forall a. (a -> a -> Bool) -> [a] -> [a] -> Bool
eqListBy TcType -> TcType -> Bool
eqType) ([[TcType]] -> [[TcType]]
canSolution [[TcType]]
a) ([[TcType]] -> [[TcType]]
canSolution [[TcType]]
b)
canSolution :: [[TcType]] -> [[TcType]]
canSolution = ([TcType] -> [TcType]) -> [[TcType]] -> [[TcType]]
forall a b. (a -> b) -> [a] -> [b]
map ((TcType -> TcType -> Ordering) -> [TcType] -> [TcType]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy TcType -> TcType -> Ordering
nonDetCmpType)
gen_soln :: DerivSpec [ThetaOrigin] -> TcM ThetaType
gen_soln :: DerivSpec [ThetaOrigin] -> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
gen_soln (DS { ds_loc :: forall theta. DerivSpec theta -> SrcSpan
ds_loc = SrcSpan
loc, ds_tvs :: forall theta. DerivSpec theta -> [TyVar]
ds_tvs = [TyVar]
tyvars
, ds_cls :: forall theta. DerivSpec theta -> Class
ds_cls = Class
clas, ds_tys :: forall theta. DerivSpec theta -> [TcType]
ds_tys = [TcType]
inst_tys, ds_theta :: forall theta. DerivSpec theta -> theta
ds_theta = [ThetaOrigin]
deriv_rhs })
= SrcSpan
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
forall a. SrcSpan -> TcRn a -> TcRn a
setSrcSpan SrcSpan
loc (IOEnv (Env TcGblEnv TcLclEnv) [TcType]
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType])
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
forall a b. (a -> b) -> a -> b
$
SDoc
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
forall a. SDoc -> TcM a -> TcM a
addErrCtxt (TcType -> SDoc
derivInstCtxt TcType
the_pred) (IOEnv (Env TcGblEnv TcLclEnv) [TcType]
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType])
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
forall a b. (a -> b) -> a -> b
$
do { [TcType]
theta <- TcType
-> [TyVar]
-> [ThetaOrigin]
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
simplifyDeriv TcType
the_pred [TyVar]
tyvars [ThetaOrigin]
deriv_rhs
; String -> SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ()
traceTc "TcDeriv" ([ThetaOrigin] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [ThetaOrigin]
deriv_rhs SDoc -> SDoc -> SDoc
$$ [TcType] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [TcType]
theta)
; [TcType] -> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
forall (m :: * -> *) a. Monad m => a -> m a
return [TcType]
theta }
where
the_pred :: TcType
the_pred = Class -> [TcType] -> TcType
mkClassPred Class
clas [TcType]
inst_tys
derivInstCtxt :: PredType -> MsgDoc
derivInstCtxt :: TcType -> SDoc
derivInstCtxt pred :: TcType
pred
= String -> SDoc
text "When deriving the instance for" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (TcType -> SDoc
forall a. Outputable a => a -> SDoc
ppr TcType
pred)
simplifyDeriv :: PredType
-> [TyVar]
-> [ThetaOrigin]
-> TcM ThetaType
simplifyDeriv :: TcType
-> [TyVar]
-> [ThetaOrigin]
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
simplifyDeriv pred :: TcType
pred tvs :: [TyVar]
tvs thetas :: [ThetaOrigin]
thetas
= do { (skol_subst :: TCvSubst
skol_subst, tvs_skols :: [TyVar]
tvs_skols) <- [TyVar] -> TcM (TCvSubst, [TyVar])
tcInstSkolTyVars [TyVar]
tvs
; let skol_set :: VarSet
skol_set = [TyVar] -> VarSet
mkVarSet [TyVar]
tvs_skols
skol_info :: SkolemInfo
skol_info = TcType -> SkolemInfo
DerivSkol TcType
pred
doc :: SDoc
doc = String -> SDoc
text "deriving" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (TcType -> SDoc
forall a. Outputable a => a -> SDoc
ppr TcType
pred)
mk_given_ev :: PredType -> TcM EvVar
mk_given_ev :: TcType -> TcM TyVar
mk_given_ev given :: TcType
given =
let given_pred :: TcType
given_pred = HasCallStack => TCvSubst -> TcType -> TcType
TCvSubst -> TcType -> TcType
substTy TCvSubst
skol_subst TcType
given
in TcType -> TcM TyVar
forall gbl lcl. TcType -> TcRnIf gbl lcl TyVar
newEvVar TcType
given_pred
emit_wanted_constraints :: [TyVar] -> [PredOrigin] -> TcM ()
emit_wanted_constraints :: [TyVar] -> [PredOrigin] -> IOEnv (Env TcGblEnv TcLclEnv) ()
emit_wanted_constraints metas_to_be :: [TyVar]
metas_to_be preds :: [PredOrigin]
preds
= do {
(meta_subst :: TCvSubst
meta_subst, _meta_tvs :: [TyVar]
_meta_tvs) <- [TyVar] -> TcM (TCvSubst, [TyVar])
newMetaTyVars [TyVar]
metas_to_be
; let wanted_subst :: TCvSubst
wanted_subst = TCvSubst
skol_subst TCvSubst -> TCvSubst -> TCvSubst
`unionTCvSubst` TCvSubst
meta_subst
mk_wanted_ct :: PredOrigin -> IOEnv (Env TcGblEnv TcLclEnv) Ct
mk_wanted_ct (PredOrigin wanted :: TcType
wanted orig :: CtOrigin
orig t_or_k :: TypeOrKind
t_or_k)
= do { CtEvidence
ev <- CtOrigin -> Maybe TypeOrKind -> TcType -> TcM CtEvidence
newWanted CtOrigin
orig (TypeOrKind -> Maybe TypeOrKind
forall a. a -> Maybe a
Just TypeOrKind
t_or_k) (TcType -> TcM CtEvidence) -> TcType -> TcM CtEvidence
forall a b. (a -> b) -> a -> b
$
TCvSubst -> TcType -> TcType
substTyUnchecked TCvSubst
wanted_subst TcType
wanted
; Ct -> IOEnv (Env TcGblEnv TcLclEnv) Ct
forall (m :: * -> *) a. Monad m => a -> m a
return (CtEvidence -> Ct
mkNonCanonical CtEvidence
ev) }
; [Ct]
cts <- (PredOrigin -> IOEnv (Env TcGblEnv TcLclEnv) Ct)
-> [PredOrigin] -> IOEnv (Env TcGblEnv TcLclEnv) [Ct]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM PredOrigin -> IOEnv (Env TcGblEnv TcLclEnv) Ct
mk_wanted_ct [PredOrigin]
preds
; Cts -> IOEnv (Env TcGblEnv TcLclEnv) ()
emitSimples ([Ct] -> Cts
listToCts [Ct]
cts) }
mk_wanteds :: ThetaOrigin -> TcM WantedConstraints
mk_wanteds :: ThetaOrigin -> TcM WantedConstraints
mk_wanteds (ThetaOrigin { to_anyclass_skols :: ThetaOrigin -> [TyVar]
to_anyclass_skols = [TyVar]
ac_skols
, to_anyclass_metas :: ThetaOrigin -> [TyVar]
to_anyclass_metas = [TyVar]
ac_metas
, to_anyclass_givens :: ThetaOrigin -> [TcType]
to_anyclass_givens = [TcType]
ac_givens
, to_wanted_origins :: ThetaOrigin -> [PredOrigin]
to_wanted_origins = [PredOrigin]
preds })
= do { [TyVar]
ac_given_evs <- (TcType -> TcM TyVar)
-> [TcType] -> IOEnv (Env TcGblEnv TcLclEnv) [TyVar]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TcType -> TcM TyVar
mk_given_ev [TcType]
ac_givens
; (_, wanteds :: WantedConstraints
wanteds)
<- TcM (TcEvBinds, ()) -> TcM ((TcEvBinds, ()), WantedConstraints)
forall a. TcM a -> TcM (a, WantedConstraints)
captureConstraints (TcM (TcEvBinds, ()) -> TcM ((TcEvBinds, ()), WantedConstraints))
-> TcM (TcEvBinds, ()) -> TcM ((TcEvBinds, ()), WantedConstraints)
forall a b. (a -> b) -> a -> b
$
SkolemInfo
-> [TyVar]
-> [TyVar]
-> IOEnv (Env TcGblEnv TcLclEnv) ()
-> TcM (TcEvBinds, ())
forall result.
SkolemInfo
-> [TyVar] -> [TyVar] -> TcM result -> TcM (TcEvBinds, result)
checkConstraints SkolemInfo
skol_info [TyVar]
ac_skols [TyVar]
ac_given_evs (IOEnv (Env TcGblEnv TcLclEnv) () -> TcM (TcEvBinds, ()))
-> IOEnv (Env TcGblEnv TcLclEnv) () -> TcM (TcEvBinds, ())
forall a b. (a -> b) -> a -> b
$
[TyVar] -> [PredOrigin] -> IOEnv (Env TcGblEnv TcLclEnv) ()
emit_wanted_constraints [TyVar]
ac_metas [PredOrigin]
preds
; WantedConstraints -> TcM WantedConstraints
forall (f :: * -> *) a. Applicative f => a -> f a
pure WantedConstraints
wanteds }
; (tc_lvl :: TcLevel
tc_lvl, wanteds :: [WantedConstraints]
wanteds) <- TcM [WantedConstraints] -> TcM (TcLevel, [WantedConstraints])
forall a. TcM a -> TcM (TcLevel, a)
pushTcLevelM (TcM [WantedConstraints] -> TcM (TcLevel, [WantedConstraints]))
-> TcM [WantedConstraints] -> TcM (TcLevel, [WantedConstraints])
forall a b. (a -> b) -> a -> b
$
(ThetaOrigin -> TcM WantedConstraints)
-> [ThetaOrigin] -> TcM [WantedConstraints]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ThetaOrigin -> TcM WantedConstraints
mk_wanteds [ThetaOrigin]
thetas
; String -> SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ()
traceTc "simplifyDeriv inputs" (SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ())
-> SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ()
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat [ [TyVar] -> SDoc
pprTyVars [TyVar]
tvs SDoc -> SDoc -> SDoc
$$ [ThetaOrigin] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [ThetaOrigin]
thetas SDoc -> SDoc -> SDoc
$$ [WantedConstraints] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [WantedConstraints]
wanteds, SDoc
doc ]
; WantedConstraints
solved_wanteds <- TcLevel -> TcM WantedConstraints -> TcM WantedConstraints
forall a. TcLevel -> TcM a -> TcM a
setTcLevel TcLevel
tc_lvl (TcM WantedConstraints -> TcM WantedConstraints)
-> TcM WantedConstraints -> TcM WantedConstraints
forall a b. (a -> b) -> a -> b
$
TcS WantedConstraints -> TcM WantedConstraints
forall a. TcS a -> TcM a
runTcSDeriveds (TcS WantedConstraints -> TcM WantedConstraints)
-> TcS WantedConstraints -> TcM WantedConstraints
forall a b. (a -> b) -> a -> b
$
WantedConstraints -> TcS WantedConstraints
solveWantedsAndDrop (WantedConstraints -> TcS WantedConstraints)
-> WantedConstraints -> TcS WantedConstraints
forall a b. (a -> b) -> a -> b
$
[WantedConstraints] -> WantedConstraints
unionsWC [WantedConstraints]
wanteds
; WantedConstraints
solved_wanteds <- WantedConstraints -> TcM WantedConstraints
zonkWC WantedConstraints
solved_wanteds
; let residual_simple :: Cts
residual_simple = Bool -> WantedConstraints -> Cts
approximateWC Bool
True WantedConstraints
solved_wanteds
(bad :: Cts
bad, good :: Bag TcType
good) = (Ct -> Either Ct TcType) -> Cts -> (Cts, Bag TcType)
forall a b c. (a -> Either b c) -> Bag a -> (Bag b, Bag c)
partitionBagWith Ct -> Either Ct TcType
get_good Cts
residual_simple
get_good :: Ct -> Either Ct PredType
get_good :: Ct -> Either Ct TcType
get_good ct :: Ct
ct | VarSet -> TcType -> Bool
validDerivPred VarSet
skol_set TcType
p
, Ct -> Bool
isWantedCt Ct
ct
= TcType -> Either Ct TcType
forall a b. b -> Either a b
Right TcType
p
| Bool
otherwise
= Ct -> Either Ct TcType
forall a b. a -> Either a b
Left Ct
ct
where p :: TcType
p = Ct -> TcType
ctPred Ct
ct
; String -> SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ()
traceTc "simplifyDeriv outputs" (SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ())
-> SDoc -> IOEnv (Env TcGblEnv TcLclEnv) ()
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat [ [TyVar] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [TyVar]
tvs_skols, Cts -> SDoc
forall a. Outputable a => a -> SDoc
ppr Cts
residual_simple, Bag TcType -> SDoc
forall a. Outputable a => a -> SDoc
ppr Bag TcType
good, Cts -> SDoc
forall a. Outputable a => a -> SDoc
ppr Cts
bad ]
; let min_theta :: [TcType]
min_theta = (TcType -> TcType) -> [TcType] -> [TcType]
forall a. (a -> TcType) -> [a] -> [a]
mkMinimalBySCs TcType -> TcType
forall a. a -> a
id (Bag TcType -> [TcType]
forall a. Bag a -> [a]
bagToList Bag TcType
good)
subst_skol :: TCvSubst
subst_skol = [TyVar] -> [TcType] -> TCvSubst
HasDebugCallStack => [TyVar] -> [TcType] -> TCvSubst
zipTvSubst [TyVar]
tvs_skols ([TcType] -> TCvSubst) -> [TcType] -> TCvSubst
forall a b. (a -> b) -> a -> b
$ [TyVar] -> [TcType]
mkTyVarTys [TyVar]
tvs
; [TyVar]
min_theta_vars <- (TcType -> TcM TyVar)
-> [TcType] -> IOEnv (Env TcGblEnv TcLclEnv) [TyVar]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TcType -> TcM TyVar
forall gbl lcl. TcType -> TcRnIf gbl lcl TyVar
newEvVar [TcType]
min_theta
; (leftover_implic :: Bag Implication
leftover_implic, _)
<- TcLevel
-> SkolemInfo
-> [TyVar]
-> [TyVar]
-> WantedConstraints
-> TcM (Bag Implication, TcEvBinds)
buildImplicationFor TcLevel
tc_lvl SkolemInfo
skol_info [TyVar]
tvs_skols
[TyVar]
min_theta_vars WantedConstraints
solved_wanteds
; Bag Implication -> IOEnv (Env TcGblEnv TcLclEnv) ()
simplifyTopImplic Bag Implication
leftover_implic
; [TcType] -> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
forall (m :: * -> *) a. Monad m => a -> m a
return (HasCallStack => TCvSubst -> [TcType] -> [TcType]
TCvSubst -> [TcType] -> [TcType]
substTheta TCvSubst
subst_skol [TcType]
min_theta) }