{-# LANGUAGE CPP, DeriveFunctor, MultiWayIf, TupleSections,
ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
module GHC.Tc.Utils.Unify (
tcWrapResult, tcWrapResultO, tcSkolemise, tcSkolemiseET,
tcSubTypeHR, tcSubTypeO, tcSubType_NC, tcSubTypeDS,
tcSubTypeDS_NC_O, tcSubTypePat,
checkConstraints, checkTvConstraints,
buildImplicationFor, emitResidualTvConstraint,
unifyType, unifyKind,
uType, promoteTcType,
swapOverTyVars, canSolveByUnification,
tcInfer,
matchExpectedListTy,
matchExpectedTyConApp,
matchExpectedAppTy,
matchExpectedFunTys,
matchActualFunTys, matchActualFunTysPart,
matchExpectedFunKind,
metaTyVarUpdateOK, occCheckForErrors, MetaTyVarUpdateResult(..)
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Hs
import GHC.Core.TyCo.Rep
import GHC.Core.TyCo.Ppr( debugPprType )
import GHC.Tc.Utils.TcMType
import GHC.Tc.Utils.Monad
import GHC.Tc.Utils.TcType
import GHC.Core.Type
import GHC.Core.Coercion
import GHC.Tc.Types.Evidence
import GHC.Tc.Types.Constraint
import GHC.Core.Predicate
import GHC.Tc.Types.Origin
import GHC.Types.Name( isSystemName )
import GHC.Tc.Utils.Instantiate
import GHC.Core.TyCon
import GHC.Builtin.Types
import GHC.Builtin.Types.Prim( tYPE )
import GHC.Types.Var as Var
import GHC.Types.Var.Set
import GHC.Types.Var.Env
import GHC.Utils.Error
import GHC.Driver.Session
import GHC.Types.Basic
import GHC.Data.Bag
import GHC.Utils.Misc
import qualified GHC.LanguageExtensions as LangExt
import GHC.Utils.Outputable as Outputable
import Data.Maybe( isNothing )
import Control.Monad
import Control.Arrow ( second )
matchExpectedFunTys :: forall a.
SDoc
-> Arity
-> ExpRhoType
-> ([ExpSigmaType] -> ExpRhoType -> TcM a)
-> TcM (a, HsWrapper)
matchExpectedFunTys :: SDoc
-> Int
-> ExpRhoType
-> ([ExpRhoType] -> ExpRhoType -> TcM a)
-> TcM (a, HsWrapper)
matchExpectedFunTys SDoc
herald Int
arity ExpRhoType
orig_ty [ExpRhoType] -> ExpRhoType -> TcM a
thing_inside
= case ExpRhoType
orig_ty of
Check TcType
ty -> [ExpRhoType] -> Int -> TcType -> TcM (a, HsWrapper)
go [] Int
arity TcType
ty
ExpRhoType
_ -> [ExpRhoType] -> Int -> ExpRhoType -> TcM (a, HsWrapper)
defer [] Int
arity ExpRhoType
orig_ty
where
go :: [ExpRhoType] -> Int -> TcType -> TcM (a, HsWrapper)
go [ExpRhoType]
acc_arg_tys Int
0 TcType
ty
= do { a
result <- [ExpRhoType] -> ExpRhoType -> TcM a
thing_inside ([ExpRhoType] -> [ExpRhoType]
forall a. [a] -> [a]
reverse [ExpRhoType]
acc_arg_tys) (TcType -> ExpRhoType
mkCheckExpType TcType
ty)
; (a, HsWrapper) -> TcM (a, HsWrapper)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (a
result, HsWrapper
idHsWrapper) }
go [ExpRhoType]
acc_arg_tys Int
n TcType
ty
| Just TcType
ty' <- TcType -> Maybe TcType
tcView TcType
ty = [ExpRhoType] -> Int -> TcType -> TcM (a, HsWrapper)
go [ExpRhoType]
acc_arg_tys Int
n TcType
ty'
go [ExpRhoType]
acc_arg_tys Int
n (FunTy { ft_af :: TcType -> AnonArgFlag
ft_af = AnonArgFlag
af, ft_arg :: TcType -> TcType
ft_arg = TcType
arg_ty, ft_res :: TcType -> TcType
ft_res = TcType
res_ty })
= ASSERT( af == VisArg )
do { (a
result, HsWrapper
wrap_res) <- [ExpRhoType] -> Int -> TcType -> TcM (a, HsWrapper)
go (TcType -> ExpRhoType
mkCheckExpType TcType
arg_ty ExpRhoType -> [ExpRhoType] -> [ExpRhoType]
forall a. a -> [a] -> [a]
: [ExpRhoType]
acc_arg_tys)
(Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
-Int
1) TcType
res_ty
; (a, HsWrapper) -> TcM (a, HsWrapper)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ( a
result
, HsWrapper -> HsWrapper -> TcType -> TcType -> SDoc -> HsWrapper
mkWpFun HsWrapper
idHsWrapper HsWrapper
wrap_res TcType
arg_ty TcType
res_ty SDoc
doc ) }
where
doc :: SDoc
doc = String -> SDoc
text String
"When inferring the argument type of a function with type" SDoc -> SDoc -> SDoc
<+>
SDoc -> SDoc
quotes (ExpRhoType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ExpRhoType
ppr ExpRhoType
orig_ty)
go [ExpRhoType]
acc_arg_tys Int
n ty :: TcType
ty@(TyVarTy TcTyVar
tv)
| TcTyVar -> Bool
isMetaTyVar TcTyVar
tv
= do { MetaDetails
cts <- TcTyVar -> TcM MetaDetails
readMetaTyVar TcTyVar
tv
; case MetaDetails
cts of
Indirect TcType
ty' -> [ExpRhoType] -> Int -> TcType -> TcM (a, HsWrapper)
go [ExpRhoType]
acc_arg_tys Int
n TcType
ty'
MetaDetails
Flexi -> [ExpRhoType] -> Int -> ExpRhoType -> TcM (a, HsWrapper)
defer [ExpRhoType]
acc_arg_tys Int
n (TcType -> ExpRhoType
mkCheckExpType TcType
ty) }
go [ExpRhoType]
acc_arg_tys Int
n TcType
ty = (TidyEnv -> TcM (TidyEnv, SDoc))
-> TcM (a, HsWrapper) -> TcM (a, HsWrapper)
forall a. (TidyEnv -> TcM (TidyEnv, SDoc)) -> TcM a -> TcM a
addErrCtxtM ([ExpRhoType] -> TcType -> TidyEnv -> TcM (TidyEnv, SDoc)
mk_ctxt [ExpRhoType]
acc_arg_tys TcType
ty) (TcM (a, HsWrapper) -> TcM (a, HsWrapper))
-> TcM (a, HsWrapper) -> TcM (a, HsWrapper)
forall a b. (a -> b) -> a -> b
$
[ExpRhoType] -> Int -> ExpRhoType -> TcM (a, HsWrapper)
defer [ExpRhoType]
acc_arg_tys Int
n (TcType -> ExpRhoType
mkCheckExpType TcType
ty)
defer :: [ExpSigmaType] -> Arity -> ExpRhoType -> TcM (a, HsWrapper)
defer :: [ExpRhoType] -> Int -> ExpRhoType -> TcM (a, HsWrapper)
defer [ExpRhoType]
acc_arg_tys Int
n ExpRhoType
fun_ty
= do { [ExpRhoType]
more_arg_tys <- Int
-> IOEnv (Env TcGblEnv TcLclEnv) ExpRhoType
-> IOEnv (Env TcGblEnv TcLclEnv) [ExpRhoType]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
External instance of the constraint type forall m. Applicative (IOEnv m)
replicateM Int
n IOEnv (Env TcGblEnv TcLclEnv) ExpRhoType
newInferExpType
; ExpRhoType
res_ty <- IOEnv (Env TcGblEnv TcLclEnv) ExpRhoType
newInferExpType
; a
result <- [ExpRhoType] -> ExpRhoType -> TcM a
thing_inside ([ExpRhoType] -> [ExpRhoType]
forall a. [a] -> [a]
reverse [ExpRhoType]
acc_arg_tys [ExpRhoType] -> [ExpRhoType] -> [ExpRhoType]
forall a. [a] -> [a] -> [a]
++ [ExpRhoType]
more_arg_tys) ExpRhoType
res_ty
; [TcType]
more_arg_tys <- (ExpRhoType -> IOEnv (Env TcGblEnv TcLclEnv) TcType)
-> [ExpRhoType] -> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
External instance of the constraint type forall m. Monad (IOEnv m)
External instance of the constraint type Traversable []
mapM ExpRhoType -> IOEnv (Env TcGblEnv TcLclEnv) TcType
readExpType [ExpRhoType]
more_arg_tys
; TcType
res_ty <- ExpRhoType -> IOEnv (Env TcGblEnv TcLclEnv) TcType
readExpType ExpRhoType
res_ty
; let unif_fun_ty :: TcType
unif_fun_ty = [TcType] -> TcType -> TcType
mkVisFunTys [TcType]
more_arg_tys TcType
res_ty
; HsWrapper
wrap <- CtOrigin -> UserTypeCtxt -> TcType -> ExpRhoType -> TcM HsWrapper
tcSubTypeDS CtOrigin
AppOrigin UserTypeCtxt
GenSigCtxt TcType
unif_fun_ty ExpRhoType
fun_ty
; (a, HsWrapper) -> TcM (a, HsWrapper)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (a
result, HsWrapper
wrap) }
mk_ctxt :: [ExpSigmaType] -> TcType -> TidyEnv -> TcM (TidyEnv, MsgDoc)
mk_ctxt :: [ExpRhoType] -> TcType -> TidyEnv -> TcM (TidyEnv, SDoc)
mk_ctxt [ExpRhoType]
arg_tys TcType
res_ty TidyEnv
env
= do { (TidyEnv
env', TcType
ty) <- TidyEnv -> TcType -> TcM (TidyEnv, TcType)
zonkTidyTcType TidyEnv
env ([TcType] -> TcType -> TcType
mkVisFunTys [TcType]
arg_tys' TcType
res_ty)
; (TidyEnv, SDoc) -> TcM (TidyEnv, SDoc)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ( TidyEnv
env', SDoc -> TcType -> Int -> SDoc
mk_fun_tys_msg SDoc
herald TcType
ty Int
arity) }
where
arg_tys' :: [TcType]
arg_tys' = (ExpRhoType -> TcType) -> [ExpRhoType] -> [TcType]
forall a b. (a -> b) -> [a] -> [b]
map (String -> ExpRhoType -> TcType
checkingExpType String
"matchExpectedFunTys") ([ExpRhoType] -> [ExpRhoType]
forall a. [a] -> [a]
reverse [ExpRhoType]
arg_tys)
matchActualFunTys :: SDoc
-> CtOrigin
-> Maybe (HsExpr GhcRn)
-> Arity
-> TcSigmaType
-> TcM (HsWrapper, [TcSigmaType], TcSigmaType)
matchActualFunTys :: SDoc
-> CtOrigin
-> Maybe (HsExpr GhcRn)
-> Int
-> TcType
-> TcM (HsWrapper, [TcType], TcType)
matchActualFunTys SDoc
herald CtOrigin
ct_orig Maybe (HsExpr GhcRn)
mb_thing Int
n_val_args_wanted TcType
fun_ty
= SDoc
-> CtOrigin
-> Maybe (HsExpr GhcRn)
-> Int
-> [TcType]
-> Int
-> TcType
-> TcM (HsWrapper, [TcType], TcType)
matchActualFunTysPart SDoc
herald CtOrigin
ct_orig Maybe (HsExpr GhcRn)
mb_thing
Int
n_val_args_wanted []
Int
n_val_args_wanted TcType
fun_ty
matchActualFunTysPart
:: SDoc
-> CtOrigin
-> Maybe (HsExpr GhcRn)
-> Arity
-> [TcSigmaType]
-> Arity
-> TcSigmaType
-> TcM (HsWrapper, [TcSigmaType], TcSigmaType)
matchActualFunTysPart :: SDoc
-> CtOrigin
-> Maybe (HsExpr GhcRn)
-> Int
-> [TcType]
-> Int
-> TcType
-> TcM (HsWrapper, [TcType], TcType)
matchActualFunTysPart SDoc
herald CtOrigin
ct_orig Maybe (HsExpr GhcRn)
mb_thing
Int
n_val_args_in_call [TcType]
arg_tys_so_far
Int
n_val_args_wanted TcType
fun_ty
= Int -> [TcType] -> TcType -> TcM (HsWrapper, [TcType], TcType)
go Int
n_val_args_wanted [TcType]
arg_tys_so_far TcType
fun_ty
where
go :: Arity
-> [TcSigmaType]
-> TcSigmaType
-> TcM (HsWrapper, [TcSigmaType], TcSigmaType)
go :: Int -> [TcType] -> TcType -> TcM (HsWrapper, [TcType], TcType)
go Int
0 [TcType]
_ TcType
ty = (HsWrapper, [TcType], TcType) -> TcM (HsWrapper, [TcType], TcType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsWrapper
idHsWrapper, [], TcType
ty)
go Int
n [TcType]
so_far TcType
ty
| Bool -> Bool
not ([TcTyVar] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [TcTyVar]
tvs Bool -> Bool -> Bool
&& [TcType] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [TcType]
theta)
= do { (HsWrapper
wrap1, TcType
rho) <- CtOrigin -> TcType -> TcM (HsWrapper, TcType)
topInstantiate CtOrigin
ct_orig TcType
ty
; (HsWrapper
wrap2, [TcType]
arg_tys, TcType
res_ty) <- Int -> [TcType] -> TcType -> TcM (HsWrapper, [TcType], TcType)
go Int
n [TcType]
so_far TcType
rho
; (HsWrapper, [TcType], TcType) -> TcM (HsWrapper, [TcType], TcType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsWrapper
wrap2 HsWrapper -> HsWrapper -> HsWrapper
<.> HsWrapper
wrap1, [TcType]
arg_tys, TcType
res_ty) }
where
([TcTyVar]
tvs, [TcType]
theta, TcType
_) = TcType -> ([TcTyVar], [TcType], TcType)
tcSplitSigmaTy TcType
ty
go Int
n [TcType]
so_far TcType
ty
| Just TcType
ty' <- TcType -> Maybe TcType
tcView TcType
ty = Int -> [TcType] -> TcType -> TcM (HsWrapper, [TcType], TcType)
go Int
n [TcType]
so_far TcType
ty'
go Int
n [TcType]
so_far (FunTy { ft_af :: TcType -> AnonArgFlag
ft_af = AnonArgFlag
af, ft_arg :: TcType -> TcType
ft_arg = TcType
arg_ty, ft_res :: TcType -> TcType
ft_res = TcType
res_ty })
= ASSERT( af == VisArg )
do { (HsWrapper
wrap_res, [TcType]
tys, TcType
ty_r) <- Int -> [TcType] -> TcType -> TcM (HsWrapper, [TcType], TcType)
go (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
-Int
1) (TcType
arg_tyTcType -> [TcType] -> [TcType]
forall a. a -> [a] -> [a]
:[TcType]
so_far) TcType
res_ty
; (HsWrapper, [TcType], TcType) -> TcM (HsWrapper, [TcType], TcType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ( HsWrapper -> HsWrapper -> TcType -> TcType -> SDoc -> HsWrapper
mkWpFun HsWrapper
idHsWrapper HsWrapper
wrap_res TcType
arg_ty TcType
ty_r SDoc
doc
, TcType
arg_ty TcType -> [TcType] -> [TcType]
forall a. a -> [a] -> [a]
: [TcType]
tys, TcType
ty_r ) }
where
doc :: SDoc
doc = String -> SDoc
text String
"When inferring the argument type of a function with type" SDoc -> SDoc -> SDoc
<+>
SDoc -> SDoc
quotes (TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
fun_ty)
go Int
n [TcType]
so_far ty :: TcType
ty@(TyVarTy TcTyVar
tv)
| TcTyVar -> Bool
isMetaTyVar TcTyVar
tv
= do { MetaDetails
cts <- TcTyVar -> TcM MetaDetails
readMetaTyVar TcTyVar
tv
; case MetaDetails
cts of
Indirect TcType
ty' -> Int -> [TcType] -> TcType -> TcM (HsWrapper, [TcType], TcType)
go Int
n [TcType]
so_far TcType
ty'
MetaDetails
Flexi -> Int -> TcType -> TcM (HsWrapper, [TcType], TcType)
defer Int
n TcType
ty }
go Int
n [TcType]
so_far TcType
ty = (TidyEnv -> TcM (TidyEnv, SDoc))
-> TcM (HsWrapper, [TcType], TcType)
-> TcM (HsWrapper, [TcType], TcType)
forall a. (TidyEnv -> TcM (TidyEnv, SDoc)) -> TcM a -> TcM a
addErrCtxtM ([TcType] -> TcType -> TidyEnv -> TcM (TidyEnv, SDoc)
mk_ctxt [TcType]
so_far TcType
ty) (Int -> TcType -> TcM (HsWrapper, [TcType], TcType)
defer Int
n TcType
ty)
defer :: Int -> TcType -> TcM (HsWrapper, [TcType], TcType)
defer Int
n TcType
fun_ty
= do { [TcType]
arg_tys <- Int
-> IOEnv (Env TcGblEnv TcLclEnv) TcType
-> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
External instance of the constraint type forall m. Applicative (IOEnv m)
replicateM Int
n IOEnv (Env TcGblEnv TcLclEnv) TcType
newOpenFlexiTyVarTy
; TcType
res_ty <- IOEnv (Env TcGblEnv TcLclEnv) TcType
newOpenFlexiTyVarTy
; let unif_fun_ty :: TcType
unif_fun_ty = [TcType] -> TcType -> TcType
mkVisFunTys [TcType]
arg_tys TcType
res_ty
; Coercion
co <- Maybe (HsExpr GhcRn) -> TcType -> TcType -> TcM Coercion
unifyType Maybe (HsExpr GhcRn)
mb_thing TcType
fun_ty TcType
unif_fun_ty
; (HsWrapper, [TcType], TcType) -> TcM (HsWrapper, [TcType], TcType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion -> HsWrapper
mkWpCastN Coercion
co, [TcType]
arg_tys, TcType
res_ty) }
mk_ctxt :: [TcType] -> TcType -> TidyEnv -> TcM (TidyEnv, MsgDoc)
mk_ctxt :: [TcType] -> TcType -> TidyEnv -> TcM (TidyEnv, SDoc)
mk_ctxt [TcType]
arg_tys TcType
res_ty TidyEnv
env
= do { (TidyEnv
env', TcType
ty) <- TidyEnv -> TcType -> TcM (TidyEnv, TcType)
zonkTidyTcType TidyEnv
env (TcType -> TcM (TidyEnv, TcType))
-> TcType -> TcM (TidyEnv, TcType)
forall a b. (a -> b) -> a -> b
$
[TcType] -> TcType -> TcType
mkVisFunTys ([TcType] -> [TcType]
forall a. [a] -> [a]
reverse [TcType]
arg_tys) TcType
res_ty
; (TidyEnv, SDoc) -> TcM (TidyEnv, SDoc)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TidyEnv
env', SDoc -> TcType -> Int -> SDoc
mk_fun_tys_msg SDoc
herald TcType
ty Int
n_val_args_in_call) }
mk_fun_tys_msg :: SDoc -> TcType -> Arity -> SDoc
mk_fun_tys_msg :: SDoc -> TcType -> Int -> SDoc
mk_fun_tys_msg SDoc
herald TcType
ty Int
n_args_in_call
| Int
n_args_in_call Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
<= Int
n_fun_args
= String -> SDoc
text String
"In the result of a function call"
| Bool
otherwise
= SDoc -> Int -> SDoc -> SDoc
hang (SDoc
herald SDoc -> SDoc -> SDoc
<+> Int -> SDoc -> SDoc
speakNOf Int
n_args_in_call (String -> SDoc
text String
"value argument") SDoc -> SDoc -> SDoc
<> SDoc
comma)
Int
2 ([SDoc] -> SDoc
sep [ String -> SDoc
text String
"but its type" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (TcType -> SDoc
pprType TcType
ty)
, if Int
n_fun_args Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Int
0 then String -> SDoc
text String
"has none"
else String -> SDoc
text String
"has only" SDoc -> SDoc -> SDoc
<+> Int -> SDoc
speakN Int
n_fun_args])
where
([TcType]
args, TcType
_) = TcType -> ([TcType], TcType)
tcSplitFunTys TcType
ty
n_fun_args :: Int
n_fun_args = [TcType] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
External instance of the constraint type Foldable []
length [TcType]
args
matchExpectedListTy :: TcRhoType -> TcM (TcCoercionN, TcRhoType)
matchExpectedListTy :: TcType -> TcM (Coercion, TcType)
matchExpectedListTy TcType
exp_ty
= do { (Coercion
co, [TcType
elt_ty]) <- TyCon -> TcType -> TcM (Coercion, [TcType])
matchExpectedTyConApp TyCon
listTyCon TcType
exp_ty
; (Coercion, TcType) -> TcM (Coercion, TcType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion
co, TcType
elt_ty) }
matchExpectedTyConApp :: TyCon
-> TcRhoType
-> TcM (TcCoercionN,
[TcSigmaType])
matchExpectedTyConApp :: TyCon -> TcType -> TcM (Coercion, [TcType])
matchExpectedTyConApp TyCon
tc TcType
orig_ty
= ASSERT(tc /= funTyCon) go orig_ty
where
go :: TcType -> TcM (Coercion, [TcType])
go TcType
ty
| Just TcType
ty' <- TcType -> Maybe TcType
tcView TcType
ty
= TcType -> TcM (Coercion, [TcType])
go TcType
ty'
go ty :: TcType
ty@(TyConApp TyCon
tycon [TcType]
args)
| TyCon
tc TyCon -> TyCon -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq TyCon
== TyCon
tycon
= (Coercion, [TcType]) -> TcM (Coercion, [TcType])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcType -> Coercion
mkTcNomReflCo TcType
ty, [TcType]
args)
go (TyVarTy TcTyVar
tv)
| TcTyVar -> Bool
isMetaTyVar TcTyVar
tv
= do { MetaDetails
cts <- TcTyVar -> TcM MetaDetails
readMetaTyVar TcTyVar
tv
; case MetaDetails
cts of
Indirect TcType
ty -> TcType -> TcM (Coercion, [TcType])
go TcType
ty
MetaDetails
Flexi -> TcM (Coercion, [TcType])
defer }
go TcType
_ = TcM (Coercion, [TcType])
defer
defer :: TcM (Coercion, [TcType])
defer
= do { (TCvSubst
_, [TcTyVar]
arg_tvs) <- [TcTyVar] -> TcM (TCvSubst, [TcTyVar])
newMetaTyVars (TyCon -> [TcTyVar]
tyConTyVars TyCon
tc)
; String -> SDoc -> TcRn ()
traceTc String
"matchExpectedTyConApp" (TyCon -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TyCon
ppr TyCon
tc SDoc -> SDoc -> SDoc
$$ [TcTyVar] -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable [a]
External instance of the constraint type Outputable TcTyVar
ppr (TyCon -> [TcTyVar]
tyConTyVars TyCon
tc) SDoc -> SDoc -> SDoc
$$ [TcTyVar] -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable [a]
External instance of the constraint type Outputable TcTyVar
ppr [TcTyVar]
arg_tvs)
; let args :: [TcType]
args = [TcTyVar] -> [TcType]
mkTyVarTys [TcTyVar]
arg_tvs
tc_template :: TcType
tc_template = TyCon -> [TcType] -> TcType
mkTyConApp TyCon
tc [TcType]
args
; Coercion
co <- Maybe (HsExpr GhcRn) -> TcType -> TcType -> TcM Coercion
unifyType Maybe (HsExpr GhcRn)
forall a. Maybe a
Nothing TcType
tc_template TcType
orig_ty
; (Coercion, [TcType]) -> TcM (Coercion, [TcType])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion
co, [TcType]
args) }
matchExpectedAppTy :: TcRhoType
-> TcM (TcCoercion,
(TcSigmaType, TcSigmaType))
matchExpectedAppTy :: TcType -> TcM (Coercion, (TcType, TcType))
matchExpectedAppTy TcType
orig_ty
= TcType -> TcM (Coercion, (TcType, TcType))
go TcType
orig_ty
where
go :: TcType -> TcM (Coercion, (TcType, TcType))
go TcType
ty
| Just TcType
ty' <- TcType -> Maybe TcType
tcView TcType
ty = TcType -> TcM (Coercion, (TcType, TcType))
go TcType
ty'
| Just (TcType
fun_ty, TcType
arg_ty) <- TcType -> Maybe (TcType, TcType)
tcSplitAppTy_maybe TcType
ty
= (Coercion, (TcType, TcType)) -> TcM (Coercion, (TcType, TcType))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcType -> Coercion
mkTcNomReflCo TcType
orig_ty, (TcType
fun_ty, TcType
arg_ty))
go (TyVarTy TcTyVar
tv)
| TcTyVar -> Bool
isMetaTyVar TcTyVar
tv
= do { MetaDetails
cts <- TcTyVar -> TcM MetaDetails
readMetaTyVar TcTyVar
tv
; case MetaDetails
cts of
Indirect TcType
ty -> TcType -> TcM (Coercion, (TcType, TcType))
go TcType
ty
MetaDetails
Flexi -> TcM (Coercion, (TcType, TcType))
defer }
go TcType
_ = TcM (Coercion, (TcType, TcType))
defer
defer :: TcM (Coercion, (TcType, TcType))
defer
= do { TcType
ty1 <- TcType -> IOEnv (Env TcGblEnv TcLclEnv) TcType
newFlexiTyVarTy TcType
kind1
; TcType
ty2 <- TcType -> IOEnv (Env TcGblEnv TcLclEnv) TcType
newFlexiTyVarTy TcType
kind2
; Coercion
co <- Maybe (HsExpr GhcRn) -> TcType -> TcType -> TcM Coercion
unifyType Maybe (HsExpr GhcRn)
forall a. Maybe a
Nothing (TcType -> TcType -> TcType
mkAppTy TcType
ty1 TcType
ty2) TcType
orig_ty
; (Coercion, (TcType, TcType)) -> TcM (Coercion, (TcType, TcType))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion
co, (TcType
ty1, TcType
ty2)) }
orig_kind :: TcType
orig_kind = HasDebugCallStack => TcType -> TcType
TcType -> TcType
External instance of the constraint type HasDebugCallStack
tcTypeKind TcType
orig_ty
kind1 :: TcType
kind1 = TcType -> TcType -> TcType
mkVisFunTy TcType
liftedTypeKind TcType
orig_kind
kind2 :: TcType
kind2 = TcType
liftedTypeKind
tcSubTypeHR :: CtOrigin
-> Maybe (HsExpr GhcRn)
-> TcSigmaType -> ExpRhoType -> TcM HsWrapper
tcSubTypeHR :: CtOrigin
-> Maybe (HsExpr GhcRn) -> TcType -> ExpRhoType -> TcM HsWrapper
tcSubTypeHR CtOrigin
orig = CtOrigin
-> UserTypeCtxt
-> Maybe (HsExpr GhcRn)
-> TcType
-> ExpRhoType
-> TcM HsWrapper
tcSubTypeDS_NC_O CtOrigin
orig UserTypeCtxt
GenSigCtxt
tcSubTypePat :: CtOrigin -> UserTypeCtxt
-> ExpSigmaType -> TcSigmaType -> TcM HsWrapper
tcSubTypePat :: CtOrigin -> UserTypeCtxt -> ExpRhoType -> TcType -> TcM HsWrapper
tcSubTypePat CtOrigin
orig UserTypeCtxt
ctxt (Check TcType
ty_actual) TcType
ty_expected
= CtOrigin
-> CtOrigin -> UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper
tc_sub_tc_type CtOrigin
eq_orig CtOrigin
orig UserTypeCtxt
ctxt TcType
ty_actual TcType
ty_expected
where
eq_orig :: CtOrigin
eq_orig = TypeEqOrigin :: TcType -> TcType -> Maybe SDoc -> Bool -> CtOrigin
TypeEqOrigin { uo_actual :: TcType
uo_actual = TcType
ty_expected
, uo_expected :: TcType
uo_expected = TcType
ty_actual
, uo_thing :: Maybe SDoc
uo_thing = Maybe SDoc
forall a. Maybe a
Nothing
, uo_visible :: Bool
uo_visible = Bool
True }
tcSubTypePat CtOrigin
_ UserTypeCtxt
_ (Infer InferResult
inf_res) TcType
ty_expected
= do { Coercion
co <- TcType -> InferResult -> TcM Coercion
fillInferResult TcType
ty_expected InferResult
inf_res
; HsWrapper -> TcM HsWrapper
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion -> HsWrapper
mkWpCastN (Coercion -> Coercion
mkTcSymCo Coercion
co)) }
tcSubTypeO :: CtOrigin
-> UserTypeCtxt
-> TcSigmaType
-> ExpRhoType
-> TcM HsWrapper
tcSubTypeO :: CtOrigin -> UserTypeCtxt -> TcType -> ExpRhoType -> TcM HsWrapper
tcSubTypeO CtOrigin
orig UserTypeCtxt
ctxt TcType
ty_actual ExpRhoType
ty_expected
= TcType -> ExpRhoType -> TcM HsWrapper -> TcM HsWrapper
forall a. TcType -> ExpRhoType -> TcM a -> TcM a
addSubTypeCtxt TcType
ty_actual ExpRhoType
ty_expected (TcM HsWrapper -> TcM HsWrapper) -> TcM HsWrapper -> TcM HsWrapper
forall a b. (a -> b) -> a -> b
$
do { String -> SDoc -> TcRn ()
traceTc String
"tcSubTypeDS_O" ([SDoc] -> SDoc
vcat [ CtOrigin -> SDoc
pprCtOrigin CtOrigin
orig
, UserTypeCtxt -> SDoc
pprUserTypeCtxt UserTypeCtxt
ctxt
, TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_actual
, ExpRhoType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ExpRhoType
ppr ExpRhoType
ty_expected ])
; CtOrigin
-> UserTypeCtxt
-> Maybe (HsExpr GhcRn)
-> TcType
-> ExpRhoType
-> TcM HsWrapper
tcSubTypeDS_NC_O CtOrigin
orig UserTypeCtxt
ctxt Maybe (HsExpr GhcRn)
forall a. Maybe a
Nothing TcType
ty_actual ExpRhoType
ty_expected }
addSubTypeCtxt :: TcType -> ExpType -> TcM a -> TcM a
addSubTypeCtxt :: TcType -> ExpRhoType -> TcM a -> TcM a
addSubTypeCtxt TcType
ty_actual ExpRhoType
ty_expected TcM a
thing_inside
| TcType -> Bool
isRhoTy TcType
ty_actual
, ExpRhoType -> Bool
isRhoExpTy ExpRhoType
ty_expected
= TcM a
thing_inside
| Bool
otherwise
= (TidyEnv -> TcM (TidyEnv, SDoc)) -> TcM a -> TcM a
forall a. (TidyEnv -> TcM (TidyEnv, SDoc)) -> TcM a -> TcM a
addErrCtxtM TidyEnv -> TcM (TidyEnv, SDoc)
mk_msg TcM a
thing_inside
where
mk_msg :: TidyEnv -> TcM (TidyEnv, SDoc)
mk_msg TidyEnv
tidy_env
= do { (TidyEnv
tidy_env, TcType
ty_actual) <- TidyEnv -> TcType -> TcM (TidyEnv, TcType)
zonkTidyTcType TidyEnv
tidy_env TcType
ty_actual
; Maybe TcType
mb_ty_expected <- ExpRhoType -> TcM (Maybe TcType)
readExpType_maybe ExpRhoType
ty_expected
; (TidyEnv
tidy_env, ExpRhoType
ty_expected) <- case Maybe TcType
mb_ty_expected of
Just TcType
ty -> (TcType -> ExpRhoType)
-> (TidyEnv, TcType) -> (TidyEnv, ExpRhoType)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
External instance of the constraint type Arrow (->)
second TcType -> ExpRhoType
mkCheckExpType ((TidyEnv, TcType) -> (TidyEnv, ExpRhoType))
-> TcM (TidyEnv, TcType)
-> IOEnv (Env TcGblEnv TcLclEnv) (TidyEnv, ExpRhoType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall env. Functor (IOEnv env)
<$>
TidyEnv -> TcType -> TcM (TidyEnv, TcType)
zonkTidyTcType TidyEnv
tidy_env TcType
ty
Maybe TcType
Nothing -> (TidyEnv, ExpRhoType)
-> IOEnv (Env TcGblEnv TcLclEnv) (TidyEnv, ExpRhoType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TidyEnv
tidy_env, ExpRhoType
ty_expected)
; TcType
ty_expected <- ExpRhoType -> IOEnv (Env TcGblEnv TcLclEnv) TcType
readExpType ExpRhoType
ty_expected
; (TidyEnv
tidy_env, TcType
ty_expected) <- TidyEnv -> TcType -> TcM (TidyEnv, TcType)
zonkTidyTcType TidyEnv
tidy_env TcType
ty_expected
; let msg :: SDoc
msg = [SDoc] -> SDoc
vcat [ SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"When checking that:")
Int
4 (TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_actual)
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"is more polymorphic than:")
Int
2 (TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_expected)) ]
; (TidyEnv, SDoc) -> TcM (TidyEnv, SDoc)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TidyEnv
tidy_env, SDoc
msg) }
tcSubType_NC :: UserTypeCtxt -> TcSigmaType -> TcSigmaType -> TcM HsWrapper
tcSubType_NC :: UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper
tcSubType_NC UserTypeCtxt
ctxt TcType
ty_actual TcType
ty_expected
= do { String -> SDoc -> TcRn ()
traceTc String
"tcSubType_NC" ([SDoc] -> SDoc
vcat [UserTypeCtxt -> SDoc
pprUserTypeCtxt UserTypeCtxt
ctxt, TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_actual, TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_expected])
; CtOrigin
-> CtOrigin -> UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper
tc_sub_tc_type CtOrigin
origin CtOrigin
origin UserTypeCtxt
ctxt TcType
ty_actual TcType
ty_expected }
where
origin :: CtOrigin
origin = TypeEqOrigin :: TcType -> TcType -> Maybe SDoc -> Bool -> CtOrigin
TypeEqOrigin { uo_actual :: TcType
uo_actual = TcType
ty_actual
, uo_expected :: TcType
uo_expected = TcType
ty_expected
, uo_thing :: Maybe SDoc
uo_thing = Maybe SDoc
forall a. Maybe a
Nothing
, uo_visible :: Bool
uo_visible = Bool
True }
tcSubTypeDS :: CtOrigin -> UserTypeCtxt -> TcSigmaType -> ExpRhoType -> TcM HsWrapper
tcSubTypeDS :: CtOrigin -> UserTypeCtxt -> TcType -> ExpRhoType -> TcM HsWrapper
tcSubTypeDS CtOrigin
orig UserTypeCtxt
ctxt TcType
ty_actual ExpRhoType
ty_expected
= TcType -> ExpRhoType -> TcM HsWrapper -> TcM HsWrapper
forall a. TcType -> ExpRhoType -> TcM a -> TcM a
addSubTypeCtxt TcType
ty_actual ExpRhoType
ty_expected (TcM HsWrapper -> TcM HsWrapper) -> TcM HsWrapper -> TcM HsWrapper
forall a b. (a -> b) -> a -> b
$
do { String -> SDoc -> TcRn ()
traceTc String
"tcSubTypeDS_NC" ([SDoc] -> SDoc
vcat [UserTypeCtxt -> SDoc
pprUserTypeCtxt UserTypeCtxt
ctxt, TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_actual, ExpRhoType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ExpRhoType
ppr ExpRhoType
ty_expected])
; CtOrigin
-> UserTypeCtxt
-> Maybe (HsExpr GhcRn)
-> TcType
-> ExpRhoType
-> TcM HsWrapper
tcSubTypeDS_NC_O CtOrigin
orig UserTypeCtxt
ctxt Maybe (HsExpr GhcRn)
forall a. Maybe a
Nothing TcType
ty_actual ExpRhoType
ty_expected }
tcSubTypeDS_NC_O :: CtOrigin
-> UserTypeCtxt
-> Maybe (HsExpr GhcRn)
-> TcSigmaType -> ExpRhoType -> TcM HsWrapper
tcSubTypeDS_NC_O :: CtOrigin
-> UserTypeCtxt
-> Maybe (HsExpr GhcRn)
-> TcType
-> ExpRhoType
-> TcM HsWrapper
tcSubTypeDS_NC_O CtOrigin
inst_orig UserTypeCtxt
ctxt Maybe (HsExpr GhcRn)
m_thing TcType
ty_actual ExpRhoType
ty_expected
= case ExpRhoType
ty_expected of
Infer InferResult
inf_res -> CtOrigin -> TcType -> InferResult -> TcM HsWrapper
instantiateAndFillInferResult CtOrigin
inst_orig TcType
ty_actual InferResult
inf_res
Check TcType
ty -> CtOrigin
-> CtOrigin -> UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper
tc_sub_type_ds CtOrigin
eq_orig CtOrigin
inst_orig UserTypeCtxt
ctxt TcType
ty_actual TcType
ty
where
eq_orig :: CtOrigin
eq_orig = TypeEqOrigin :: TcType -> TcType -> Maybe SDoc -> Bool -> CtOrigin
TypeEqOrigin { uo_actual :: TcType
uo_actual = TcType
ty_actual, uo_expected :: TcType
uo_expected = TcType
ty
, uo_thing :: Maybe SDoc
uo_thing = HsExpr GhcRn -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall (p :: Pass).
OutputableBndrId p =>
Outputable (HsExpr (GhcPass p))
External instance of the constraint type OutputableBndr Name
External instance of the constraint type OutputableBndr Name
External instance of the constraint type IsPass 'Renamed
ppr (HsExpr GhcRn -> SDoc) -> Maybe (HsExpr GhcRn) -> Maybe SDoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
<$> Maybe (HsExpr GhcRn)
m_thing
, uo_visible :: Bool
uo_visible = Bool
True }
tc_sub_tc_type :: CtOrigin
-> CtOrigin
-> UserTypeCtxt -> TcSigmaType -> TcSigmaType -> TcM HsWrapper
tc_sub_tc_type :: CtOrigin
-> CtOrigin -> UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper
tc_sub_tc_type CtOrigin
eq_orig CtOrigin
inst_orig UserTypeCtxt
ctxt TcType
ty_actual TcType
ty_expected
| TcType -> Bool
definitely_poly TcType
ty_expected
, Bool -> Bool
not (TcType -> Bool
possibly_poly TcType
ty_actual)
= do { String -> SDoc -> TcRn ()
traceTc String
"tc_sub_tc_type (drop to equality)" (SDoc -> TcRn ()) -> SDoc -> TcRn ()
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat [ String -> SDoc
text String
"ty_actual =" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_actual
, String -> SDoc
text String
"ty_expected =" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_expected ]
; Coercion -> HsWrapper
mkWpCastN (Coercion -> HsWrapper) -> TcM Coercion -> TcM HsWrapper
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall env. Functor (IOEnv env)
<$>
TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
TypeLevel CtOrigin
eq_orig TcType
ty_actual TcType
ty_expected }
| Bool
otherwise
= do { String -> SDoc -> TcRn ()
traceTc String
"tc_sub_tc_type (general case)" (SDoc -> TcRn ()) -> SDoc -> TcRn ()
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat [ String -> SDoc
text String
"ty_actual =" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_actual
, String -> SDoc
text String
"ty_expected =" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_expected ]
; (HsWrapper
sk_wrap, HsWrapper
inner_wrap) <- UserTypeCtxt
-> TcType
-> ([TcTyVar] -> TcType -> TcM HsWrapper)
-> TcM (HsWrapper, HsWrapper)
forall result.
UserTypeCtxt
-> TcType
-> ([TcTyVar] -> TcType -> TcM result)
-> TcM (HsWrapper, result)
tcSkolemise UserTypeCtxt
ctxt TcType
ty_expected (([TcTyVar] -> TcType -> TcM HsWrapper)
-> TcM (HsWrapper, HsWrapper))
-> ([TcTyVar] -> TcType -> TcM HsWrapper)
-> TcM (HsWrapper, HsWrapper)
forall a b. (a -> b) -> a -> b
$
\ [TcTyVar]
_ TcType
sk_rho ->
CtOrigin
-> CtOrigin -> UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper
tc_sub_type_ds CtOrigin
eq_orig CtOrigin
inst_orig UserTypeCtxt
ctxt
TcType
ty_actual TcType
sk_rho
; HsWrapper -> TcM HsWrapper
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsWrapper
sk_wrap HsWrapper -> HsWrapper -> HsWrapper
<.> HsWrapper
inner_wrap) }
where
possibly_poly :: TcType -> Bool
possibly_poly TcType
ty
| TcType -> Bool
isForAllTy TcType
ty = Bool
True
| Just (TcType
_, TcType
res) <- TcType -> Maybe (TcType, TcType)
splitFunTy_maybe TcType
ty = TcType -> Bool
possibly_poly TcType
res
| Bool
otherwise = Bool
False
definitely_poly :: TcType -> Bool
definitely_poly TcType
ty
| ([TcTyVar]
tvs, [TcType]
theta, TcType
tau) <- TcType -> ([TcTyVar], [TcType], TcType)
tcSplitSigmaTy TcType
ty
, (TcTyVar
tv:[TcTyVar]
_) <- [TcTyVar]
tvs
, [TcType] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [TcType]
theta
, EqRel -> TcTyVar -> TcType -> Bool
isInsolubleOccursCheck EqRel
NomEq TcTyVar
tv TcType
tau
= Bool
True
| Bool
otherwise
= Bool
False
tc_sub_type_ds :: CtOrigin
-> CtOrigin
-> UserTypeCtxt -> TcSigmaType -> TcRhoType -> TcM HsWrapper
tc_sub_type_ds :: CtOrigin
-> CtOrigin -> UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper
tc_sub_type_ds CtOrigin
eq_orig CtOrigin
inst_orig UserTypeCtxt
ctxt TcType
ty_actual TcType
ty_expected
= do { String -> SDoc -> TcRn ()
traceTc String
"tc_sub_type_ds" (SDoc -> TcRn ()) -> SDoc -> TcRn ()
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat [ String -> SDoc
text String
"ty_actual =" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_actual
, String -> SDoc
text String
"ty_expected =" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_expected ]
; TcType -> TcType -> TcM HsWrapper
go TcType
ty_actual TcType
ty_expected }
where
go :: TcType -> TcType -> TcM HsWrapper
go TcType
ty_a TcType
ty_e | Just TcType
ty_a' <- TcType -> Maybe TcType
tcView TcType
ty_a = TcType -> TcType -> TcM HsWrapper
go TcType
ty_a' TcType
ty_e
| Just TcType
ty_e' <- TcType -> Maybe TcType
tcView TcType
ty_e = TcType -> TcType -> TcM HsWrapper
go TcType
ty_a TcType
ty_e'
go (TyVarTy TcTyVar
tv_a) TcType
ty_e
= do { LookupTyVarResult
lookup_res <- TcTyVar -> TcM LookupTyVarResult
lookupTcTyVar TcTyVar
tv_a
; case LookupTyVarResult
lookup_res of
Filled TcType
ty_a' ->
do { String -> SDoc -> TcRn ()
traceTc String
"tcSubTypeDS_NC_O following filled act meta-tyvar:"
(TcTyVar -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcTyVar
ppr TcTyVar
tv_a SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"-->" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_a')
; CtOrigin
-> CtOrigin -> UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper
tc_sub_type_ds CtOrigin
eq_orig CtOrigin
inst_orig UserTypeCtxt
ctxt TcType
ty_a' TcType
ty_e }
Unfilled TcTyVarDetails
_ -> TcM HsWrapper
unify }
go (FunTy { ft_af :: TcType -> AnonArgFlag
ft_af = AnonArgFlag
VisArg, ft_arg :: TcType -> TcType
ft_arg = TcType
act_arg, ft_res :: TcType -> TcType
ft_res = TcType
act_res })
(FunTy { ft_af :: TcType -> AnonArgFlag
ft_af = AnonArgFlag
VisArg, ft_arg :: TcType -> TcType
ft_arg = TcType
exp_arg, ft_res :: TcType -> TcType
ft_res = TcType
exp_res })
=
do { HsWrapper
res_wrap <- CtOrigin
-> CtOrigin -> UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper
tc_sub_type_ds CtOrigin
eq_orig CtOrigin
inst_orig UserTypeCtxt
ctxt TcType
act_res TcType
exp_res
; HsWrapper
arg_wrap <- CtOrigin
-> CtOrigin -> UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper
tc_sub_tc_type CtOrigin
eq_orig CtOrigin
given_orig UserTypeCtxt
GenSigCtxt TcType
exp_arg TcType
act_arg
; HsWrapper -> TcM HsWrapper
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsWrapper -> HsWrapper -> TcType -> TcType -> SDoc -> HsWrapper
mkWpFun HsWrapper
arg_wrap HsWrapper
res_wrap TcType
exp_arg TcType
exp_res SDoc
doc) }
where
given_orig :: CtOrigin
given_orig = SkolemInfo -> CtOrigin
GivenOrigin (UserTypeCtxt -> TcType -> [(Name, TcTyVar)] -> SkolemInfo
SigSkol UserTypeCtxt
GenSigCtxt TcType
exp_arg [])
doc :: SDoc
doc = String -> SDoc
text String
"When checking that" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_actual) SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"is more polymorphic than" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_expected)
go TcType
ty_a TcType
ty_e
| let ([TcTyVar]
tvs, [TcType]
theta, TcType
_) = TcType -> ([TcTyVar], [TcType], TcType)
tcSplitSigmaTy TcType
ty_a
, Bool -> Bool
not ([TcTyVar] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [TcTyVar]
tvs Bool -> Bool -> Bool
&& [TcType] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [TcType]
theta)
= do { (HsWrapper
in_wrap, TcType
in_rho) <- CtOrigin -> TcType -> TcM (HsWrapper, TcType)
topInstantiate CtOrigin
inst_orig TcType
ty_a
; HsWrapper
body_wrap <- CtOrigin
-> CtOrigin -> UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper
tc_sub_type_ds
(CtOrigin
eq_orig { uo_actual :: TcType
uo_actual = TcType
in_rho
, uo_expected :: TcType
uo_expected = TcType
ty_expected })
CtOrigin
inst_orig UserTypeCtxt
ctxt TcType
in_rho TcType
ty_e
; HsWrapper -> TcM HsWrapper
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsWrapper
body_wrap HsWrapper -> HsWrapper -> HsWrapper
<.> HsWrapper
in_wrap) }
| Bool
otherwise
= TcM HsWrapper
inst_and_unify
inst_and_unify :: TcM HsWrapper
inst_and_unify = do { (HsWrapper
wrap, TcType
rho_a) <- CtOrigin -> TcType -> TcM (HsWrapper, TcType)
deeplyInstantiate CtOrigin
inst_orig TcType
ty_actual
; let eq_orig' :: CtOrigin
eq_orig' = case CtOrigin
eq_orig of
TypeEqOrigin { uo_actual :: CtOrigin -> TcType
uo_actual = TcType
orig_ty_actual }
| TcType
orig_ty_actual HasDebugCallStack => TcType -> TcType -> Bool
TcType -> TcType -> Bool
External instance of the constraint type HasDebugCallStack
`tcEqType` TcType
ty_actual
, Bool -> Bool
not (HsWrapper -> Bool
isIdHsWrapper HsWrapper
wrap)
-> CtOrigin
eq_orig { uo_actual :: TcType
uo_actual = TcType
rho_a }
CtOrigin
_ -> CtOrigin
eq_orig
; Coercion
cow <- TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
TypeLevel CtOrigin
eq_orig' TcType
rho_a TcType
ty_expected
; HsWrapper -> TcM HsWrapper
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion -> HsWrapper
mkWpCastN Coercion
cow HsWrapper -> HsWrapper -> HsWrapper
<.> HsWrapper
wrap) }
unify :: TcM HsWrapper
unify = Coercion -> HsWrapper
mkWpCastN (Coercion -> HsWrapper) -> TcM Coercion -> TcM HsWrapper
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall env. Functor (IOEnv env)
<$> TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
TypeLevel CtOrigin
eq_orig TcType
ty_actual TcType
ty_expected
tcWrapResult :: HsExpr GhcRn -> HsExpr GhcTcId -> TcSigmaType -> ExpRhoType
-> TcM (HsExpr GhcTcId)
tcWrapResult :: HsExpr GhcRn
-> HsExpr GhcTcId -> TcType -> ExpRhoType -> TcM (HsExpr GhcTcId)
tcWrapResult HsExpr GhcRn
rn_expr = CtOrigin
-> HsExpr GhcRn
-> HsExpr GhcTcId
-> TcType
-> ExpRhoType
-> TcM (HsExpr GhcTcId)
tcWrapResultO (HsExpr GhcRn -> CtOrigin
exprCtOrigin HsExpr GhcRn
rn_expr) HsExpr GhcRn
rn_expr
tcWrapResultO :: CtOrigin -> HsExpr GhcRn -> HsExpr GhcTcId -> TcSigmaType -> ExpRhoType
-> TcM (HsExpr GhcTcId)
tcWrapResultO :: CtOrigin
-> HsExpr GhcRn
-> HsExpr GhcTcId
-> TcType
-> ExpRhoType
-> TcM (HsExpr GhcTcId)
tcWrapResultO CtOrigin
orig HsExpr GhcRn
rn_expr HsExpr GhcTcId
expr TcType
actual_ty ExpRhoType
res_ty
= do { String -> SDoc -> TcRn ()
traceTc String
"tcWrapResult" ([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"Actual: " SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
actual_ty
, String -> SDoc
text String
"Expected:" SDoc -> SDoc -> SDoc
<+> ExpRhoType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ExpRhoType
ppr ExpRhoType
res_ty ])
; HsWrapper
cow <- CtOrigin
-> UserTypeCtxt
-> Maybe (HsExpr GhcRn)
-> TcType
-> ExpRhoType
-> TcM HsWrapper
tcSubTypeDS_NC_O CtOrigin
orig UserTypeCtxt
GenSigCtxt
(HsExpr GhcRn -> Maybe (HsExpr GhcRn)
forall a. a -> Maybe a
Just HsExpr GhcRn
rn_expr) TcType
actual_ty ExpRhoType
res_ty
; HsExpr GhcTcId -> TcM (HsExpr GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsWrapper -> HsExpr GhcTcId -> HsExpr GhcTcId
mkHsWrap HsWrapper
cow HsExpr GhcTcId
expr) }
tcInfer :: (ExpSigmaType -> TcM a) -> TcM (a, TcSigmaType)
tcInfer :: (ExpRhoType -> TcM a) -> TcM (a, TcType)
tcInfer ExpRhoType -> TcM a
tc_check
= do { ExpRhoType
res_ty <- IOEnv (Env TcGblEnv TcLclEnv) ExpRhoType
newInferExpType
; a
result <- ExpRhoType -> TcM a
tc_check ExpRhoType
res_ty
; TcType
res_ty <- ExpRhoType -> IOEnv (Env TcGblEnv TcLclEnv) TcType
readExpType ExpRhoType
res_ty
; (a, TcType) -> TcM (a, TcType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (a
result, TcType
res_ty) }
instantiateAndFillInferResult :: CtOrigin -> TcType -> InferResult -> TcM HsWrapper
instantiateAndFillInferResult :: CtOrigin -> TcType -> InferResult -> TcM HsWrapper
instantiateAndFillInferResult CtOrigin
orig TcType
ty InferResult
inf_res
= do { (HsWrapper
wrap, TcType
rho) <- CtOrigin -> TcType -> TcM (HsWrapper, TcType)
deeplyInstantiate CtOrigin
orig TcType
ty
; Coercion
co <- TcType -> InferResult -> TcM Coercion
fillInferResult TcType
rho InferResult
inf_res
; HsWrapper -> TcM HsWrapper
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion -> HsWrapper
mkWpCastN Coercion
co HsWrapper -> HsWrapper -> HsWrapper
<.> HsWrapper
wrap) }
fillInferResult :: TcType -> InferResult -> TcM TcCoercionN
fillInferResult :: TcType -> InferResult -> TcM Coercion
fillInferResult TcType
orig_ty (IR { ir_uniq :: InferResult -> Unique
ir_uniq = Unique
u, ir_lvl :: InferResult -> TcLevel
ir_lvl = TcLevel
res_lvl
, ir_ref :: InferResult -> IORef (Maybe TcType)
ir_ref = IORef (Maybe TcType)
ref })
= do { (Coercion
ty_co, TcType
ty_to_fill_with) <- TcLevel -> TcType -> TcM (Coercion, TcType)
promoteTcType TcLevel
res_lvl TcType
orig_ty
; String -> SDoc -> TcRn ()
traceTc String
"Filling ExpType" (SDoc -> TcRn ()) -> SDoc -> TcRn ()
forall a b. (a -> b) -> a -> b
$
Unique -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Unique
ppr Unique
u SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
":=" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty_to_fill_with
; Bool -> TcRn () -> TcRn ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type forall m. Applicative (IOEnv m)
when Bool
debugIsOn (TcType -> TcRn ()
forall {gbl} {lcl}. TcType -> IOEnv (Env gbl lcl) ()
check_hole TcType
ty_to_fill_with)
; IORef (Maybe TcType) -> Maybe TcType -> TcRn ()
forall a gbl lcl. TcRef a -> a -> TcRnIf gbl lcl ()
writeTcRef IORef (Maybe TcType)
ref (TcType -> Maybe TcType
forall a. a -> Maybe a
Just TcType
ty_to_fill_with)
; Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return Coercion
ty_co }
where
check_hole :: TcType -> IOEnv (Env gbl lcl) ()
check_hole TcType
ty
= do { let ty_lvl :: TcLevel
ty_lvl = TcType -> TcLevel
tcTypeLevel TcType
ty
; MASSERT2( not (ty_lvl `strictlyDeeperThan` res_lvl),
ppr u $$ ppr res_lvl $$ ppr ty_lvl $$
ppr ty <+> dcolon <+> ppr (tcTypeKind ty) $$ ppr orig_ty )
; Maybe TcType
cts <- IORef (Maybe TcType) -> TcRnIf gbl lcl (Maybe TcType)
forall a gbl lcl. TcRef a -> TcRnIf gbl lcl a
readTcRef IORef (Maybe TcType)
ref
; case Maybe TcType
cts of
Just TcType
already_there -> String -> SDoc -> IOEnv (Env gbl lcl) ()
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"writeExpType"
([SDoc] -> SDoc
vcat [ Unique -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Unique
ppr Unique
u
, TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty
, TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
already_there ])
Maybe TcType
Nothing -> () -> IOEnv (Env gbl lcl) ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return () }
promoteTcType :: TcLevel -> TcType -> TcM (TcCoercion, TcType)
promoteTcType :: TcLevel -> TcType -> TcM (Coercion, TcType)
promoteTcType TcLevel
dest_lvl TcType
ty
= do { TcLevel
cur_lvl <- TcM TcLevel
getTcLevel
; if (TcLevel
cur_lvl TcLevel -> TcLevel -> Bool
`sameDepthAs` TcLevel
dest_lvl)
then TcM (Coercion, TcType)
dont_promote_it
else TcM (Coercion, TcType)
promote_it }
where
promote_it :: TcM (TcCoercion, TcType)
promote_it :: TcM (Coercion, TcType)
promote_it
= do { TcType
rr <- TcLevel -> TcType -> IOEnv (Env TcGblEnv TcLclEnv) TcType
newMetaTyVarTyAtLevel TcLevel
dest_lvl TcType
runtimeRepTy
; TcType
prom_ty <- TcLevel -> TcType -> IOEnv (Env TcGblEnv TcLclEnv) TcType
newMetaTyVarTyAtLevel TcLevel
dest_lvl (TcType -> TcType
tYPE TcType
rr)
; let eq_orig :: CtOrigin
eq_orig = TypeEqOrigin :: TcType -> TcType -> Maybe SDoc -> Bool -> CtOrigin
TypeEqOrigin { uo_actual :: TcType
uo_actual = TcType
ty
, uo_expected :: TcType
uo_expected = TcType
prom_ty
, uo_thing :: Maybe SDoc
uo_thing = Maybe SDoc
forall a. Maybe a
Nothing
, uo_visible :: Bool
uo_visible = Bool
False }
; Coercion
co <- CtOrigin -> TypeOrKind -> Role -> TcType -> TcType -> TcM Coercion
emitWantedEq CtOrigin
eq_orig TypeOrKind
TypeLevel Role
Nominal TcType
ty TcType
prom_ty
; (Coercion, TcType) -> TcM (Coercion, TcType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion
co, TcType
prom_ty) }
dont_promote_it :: TcM (TcCoercion, TcType)
dont_promote_it :: TcM (Coercion, TcType)
dont_promote_it
= do { TcType
res_kind <- IOEnv (Env TcGblEnv TcLclEnv) TcType
newOpenTypeKind
; let ty_kind :: TcType
ty_kind = HasDebugCallStack => TcType -> TcType
TcType -> TcType
External instance of the constraint type HasDebugCallStack
tcTypeKind TcType
ty
kind_orig :: CtOrigin
kind_orig = TypeEqOrigin :: TcType -> TcType -> Maybe SDoc -> Bool -> CtOrigin
TypeEqOrigin { uo_actual :: TcType
uo_actual = TcType
ty_kind
, uo_expected :: TcType
uo_expected = TcType
res_kind
, uo_thing :: Maybe SDoc
uo_thing = Maybe SDoc
forall a. Maybe a
Nothing
, uo_visible :: Bool
uo_visible = Bool
False }
; Coercion
ki_co <- TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
KindLevel CtOrigin
kind_orig (HasDebugCallStack => TcType -> TcType
TcType -> TcType
External instance of the constraint type HasDebugCallStack
tcTypeKind TcType
ty) TcType
res_kind
; let co :: Coercion
co = Role -> TcType -> Coercion -> Coercion
mkTcGReflRightCo Role
Nominal TcType
ty Coercion
ki_co
; (Coercion, TcType) -> TcM (Coercion, TcType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion
co, TcType
ty TcType -> Coercion -> TcType
`mkCastTy` Coercion
ki_co) }
tcSkolemise :: UserTypeCtxt -> TcSigmaType
-> ([TcTyVar] -> TcType -> TcM result)
-> TcM (HsWrapper, result)
tcSkolemise :: UserTypeCtxt
-> TcType
-> ([TcTyVar] -> TcType -> TcM result)
-> TcM (HsWrapper, result)
tcSkolemise UserTypeCtxt
ctxt TcType
expected_ty [TcTyVar] -> TcType -> TcM result
thing_inside
= do { String -> SDoc -> TcRn ()
traceTc String
"tcSkolemise" SDoc
Outputable.empty
; (HsWrapper
wrap, [(Name, TcTyVar)]
tv_prs, [TcTyVar]
given, TcType
rho') <- TcType -> TcM (HsWrapper, [(Name, TcTyVar)], [TcTyVar], TcType)
deeplySkolemise TcType
expected_ty
; TcLevel
lvl <- TcM TcLevel
getTcLevel
; Bool -> TcRn () -> TcRn ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type forall m. Applicative (IOEnv m)
when Bool
debugIsOn (TcRn () -> TcRn ()) -> TcRn () -> TcRn ()
forall a b. (a -> b) -> a -> b
$
String -> SDoc -> TcRn ()
traceTc String
"tcSkolemise" (SDoc -> TcRn ()) -> SDoc -> TcRn ()
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat [
TcLevel -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcLevel
ppr TcLevel
lvl,
String -> SDoc
text String
"expected_ty" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
expected_ty,
String -> SDoc
text String
"inst tyvars" SDoc -> SDoc -> SDoc
<+> [(Name, TcTyVar)] -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable [a]
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 TcTyVar
ppr [(Name, TcTyVar)]
tv_prs,
String -> SDoc
text String
"given" SDoc -> SDoc -> SDoc
<+> [TcTyVar] -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable [a]
External instance of the constraint type Outputable TcTyVar
ppr [TcTyVar]
given,
String -> SDoc
text String
"inst type" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
rho' ]
; let tvs' :: [TcTyVar]
tvs' = ((Name, TcTyVar) -> TcTyVar) -> [(Name, TcTyVar)] -> [TcTyVar]
forall a b. (a -> b) -> [a] -> [b]
map (Name, TcTyVar) -> TcTyVar
forall a b. (a, b) -> b
snd [(Name, TcTyVar)]
tv_prs
skol_info :: SkolemInfo
skol_info = UserTypeCtxt -> TcType -> [(Name, TcTyVar)] -> SkolemInfo
SigSkol UserTypeCtxt
ctxt TcType
expected_ty [(Name, TcTyVar)]
tv_prs
; (TcEvBinds
ev_binds, result
result) <- SkolemInfo
-> [TcTyVar] -> [TcTyVar] -> TcM result -> TcM (TcEvBinds, result)
forall result.
SkolemInfo
-> [TcTyVar] -> [TcTyVar] -> TcM result -> TcM (TcEvBinds, result)
checkConstraints SkolemInfo
skol_info [TcTyVar]
tvs' [TcTyVar]
given (TcM result -> TcM (TcEvBinds, result))
-> TcM result -> TcM (TcEvBinds, result)
forall a b. (a -> b) -> a -> b
$
[TcTyVar] -> TcType -> TcM result
thing_inside [TcTyVar]
tvs' TcType
rho'
; (HsWrapper, result) -> TcM (HsWrapper, result)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsWrapper
wrap HsWrapper -> HsWrapper -> HsWrapper
<.> TcEvBinds -> HsWrapper
mkWpLet TcEvBinds
ev_binds, result
result) }
tcSkolemiseET :: UserTypeCtxt -> ExpSigmaType
-> (ExpRhoType -> TcM result)
-> TcM (HsWrapper, result)
tcSkolemiseET :: UserTypeCtxt
-> ExpRhoType
-> (ExpRhoType -> TcM result)
-> TcM (HsWrapper, result)
tcSkolemiseET UserTypeCtxt
_ et :: ExpRhoType
et@(Infer {}) ExpRhoType -> TcM result
thing_inside
= (HsWrapper
idHsWrapper, ) (result -> (HsWrapper, result))
-> TcM result -> TcM (HsWrapper, result)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall env. Functor (IOEnv env)
<$> ExpRhoType -> TcM result
thing_inside ExpRhoType
et
tcSkolemiseET UserTypeCtxt
ctxt (Check TcType
ty) ExpRhoType -> TcM result
thing_inside
= UserTypeCtxt
-> TcType
-> ([TcTyVar] -> TcType -> TcM result)
-> TcM (HsWrapper, result)
forall result.
UserTypeCtxt
-> TcType
-> ([TcTyVar] -> TcType -> TcM result)
-> TcM (HsWrapper, result)
tcSkolemise UserTypeCtxt
ctxt TcType
ty (([TcTyVar] -> TcType -> TcM result) -> TcM (HsWrapper, result))
-> ([TcTyVar] -> TcType -> TcM result) -> TcM (HsWrapper, result)
forall a b. (a -> b) -> a -> b
$ \[TcTyVar]
_ -> ExpRhoType -> TcM result
thing_inside (ExpRhoType -> TcM result)
-> (TcType -> ExpRhoType) -> TcType -> TcM result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TcType -> ExpRhoType
mkCheckExpType
checkConstraints :: SkolemInfo
-> [TcTyVar]
-> [EvVar]
-> TcM result
-> TcM (TcEvBinds, result)
checkConstraints :: SkolemInfo
-> [TcTyVar] -> [TcTyVar] -> TcM result -> TcM (TcEvBinds, result)
checkConstraints SkolemInfo
skol_info [TcTyVar]
skol_tvs [TcTyVar]
given TcM result
thing_inside
= do { Bool
implication_needed <- SkolemInfo -> [TcTyVar] -> [TcTyVar] -> TcM Bool
implicationNeeded SkolemInfo
skol_info [TcTyVar]
skol_tvs [TcTyVar]
given
; if Bool
implication_needed
then do { (TcLevel
tclvl, WantedConstraints
wanted, result
result) <- TcM result -> TcM (TcLevel, WantedConstraints, result)
forall a. TcM a -> TcM (TcLevel, WantedConstraints, a)
pushLevelAndCaptureConstraints TcM result
thing_inside
; (Bag Implication
implics, TcEvBinds
ev_binds) <- TcLevel
-> SkolemInfo
-> [TcTyVar]
-> [TcTyVar]
-> WantedConstraints
-> TcM (Bag Implication, TcEvBinds)
buildImplicationFor TcLevel
tclvl SkolemInfo
skol_info [TcTyVar]
skol_tvs [TcTyVar]
given WantedConstraints
wanted
; String -> SDoc -> TcRn ()
traceTc String
"checkConstraints" (TcLevel -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcLevel
ppr TcLevel
tclvl SDoc -> SDoc -> SDoc
$$ [TcTyVar] -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable [a]
External instance of the constraint type Outputable TcTyVar
ppr [TcTyVar]
skol_tvs)
; Bag Implication -> TcRn ()
emitImplications Bag Implication
implics
; (TcEvBinds, result) -> TcM (TcEvBinds, result)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcEvBinds
ev_binds, result
result) }
else
do { result
res <- TcM result
thing_inside
; (TcEvBinds, result) -> TcM (TcEvBinds, result)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcEvBinds
emptyTcEvBinds, result
res) } }
checkTvConstraints :: SkolemInfo
-> [TcTyVar]
-> TcM result
-> TcM result
checkTvConstraints :: SkolemInfo -> [TcTyVar] -> TcM result -> TcM result
checkTvConstraints SkolemInfo
skol_info [TcTyVar]
skol_tvs TcM result
thing_inside
= do { (TcLevel
tclvl, WantedConstraints
wanted, result
result) <- TcM result -> TcM (TcLevel, WantedConstraints, result)
forall a. TcM a -> TcM (TcLevel, WantedConstraints, a)
pushLevelAndCaptureConstraints TcM result
thing_inside
; SkolemInfo
-> Maybe SDoc
-> [TcTyVar]
-> TcLevel
-> WantedConstraints
-> TcRn ()
emitResidualTvConstraint SkolemInfo
skol_info Maybe SDoc
forall a. Maybe a
Nothing [TcTyVar]
skol_tvs TcLevel
tclvl WantedConstraints
wanted
; result -> TcM result
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return result
result }
emitResidualTvConstraint :: SkolemInfo -> Maybe SDoc -> [TcTyVar]
-> TcLevel -> WantedConstraints -> TcM ()
emitResidualTvConstraint :: SkolemInfo
-> Maybe SDoc
-> [TcTyVar]
-> TcLevel
-> WantedConstraints
-> TcRn ()
emitResidualTvConstraint SkolemInfo
skol_info Maybe SDoc
m_telescope [TcTyVar]
skol_tvs TcLevel
tclvl WantedConstraints
wanted
| WantedConstraints -> Bool
isEmptyWC WantedConstraints
wanted
, Maybe SDoc -> Bool
forall a. Maybe a -> Bool
isNothing Maybe SDoc
m_telescope Bool -> Bool -> Bool
|| [TcTyVar]
skol_tvs [TcTyVar] -> Int -> Bool
forall a. [a] -> Int -> Bool
`lengthAtMost` Int
1
= () -> TcRn ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ()
| Bool
otherwise
= do { EvBindsVar
ev_binds <- TcM EvBindsVar
newNoTcEvBinds
; Implication
implic <- TcM Implication
newImplication
; let status :: ImplicStatus
status | WantedConstraints -> Bool
insolubleWC WantedConstraints
wanted = ImplicStatus
IC_Insoluble
| Bool
otherwise = ImplicStatus
IC_Unsolved
; Implication -> TcRn ()
emitImplication (Implication -> TcRn ()) -> Implication -> TcRn ()
forall a b. (a -> b) -> a -> b
$
Implication
implic { ic_status :: ImplicStatus
ic_status = ImplicStatus
status
, ic_tclvl :: TcLevel
ic_tclvl = TcLevel
tclvl
, ic_skols :: [TcTyVar]
ic_skols = [TcTyVar]
skol_tvs
, ic_no_eqs :: Bool
ic_no_eqs = Bool
True
, ic_telescope :: Maybe SDoc
ic_telescope = Maybe SDoc
m_telescope
, ic_wanted :: WantedConstraints
ic_wanted = WantedConstraints
wanted
, ic_binds :: EvBindsVar
ic_binds = EvBindsVar
ev_binds
, ic_info :: SkolemInfo
ic_info = SkolemInfo
skol_info } }
implicationNeeded :: SkolemInfo -> [TcTyVar] -> [EvVar] -> TcM Bool
implicationNeeded :: SkolemInfo -> [TcTyVar] -> [TcTyVar] -> TcM Bool
implicationNeeded SkolemInfo
skol_info [TcTyVar]
skol_tvs [TcTyVar]
given
| [TcTyVar] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [TcTyVar]
skol_tvs
, [TcTyVar] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [TcTyVar]
given
, Bool -> Bool
not (SkolemInfo -> Bool
alwaysBuildImplication SkolemInfo
skol_info)
=
do { TcLevel
tc_lvl <- TcM TcLevel
getTcLevel
; if Bool -> Bool
not (TcLevel -> Bool
isTopTcLevel TcLevel
tc_lvl)
then Bool -> TcM Bool
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return Bool
False
else
do { DynFlags
dflags <- IOEnv (Env TcGblEnv TcLclEnv) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type forall env. ContainsDynFlags env => HasDynFlags (IOEnv env)
External instance of the constraint type forall gbl lcl. ContainsDynFlags (Env gbl lcl)
getDynFlags
; Bool -> TcM Bool
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_DeferTypeErrors DynFlags
dflags Bool -> Bool -> Bool
||
GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_DeferTypedHoles DynFlags
dflags Bool -> Bool -> Bool
||
GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_DeferOutOfScopeVariables DynFlags
dflags) } }
| Bool
otherwise
= Bool -> TcM Bool
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return Bool
True
alwaysBuildImplication :: SkolemInfo -> Bool
alwaysBuildImplication :: SkolemInfo -> Bool
alwaysBuildImplication SkolemInfo
_ = Bool
False
buildImplicationFor :: TcLevel -> SkolemInfo -> [TcTyVar]
-> [EvVar] -> WantedConstraints
-> TcM (Bag Implication, TcEvBinds)
buildImplicationFor :: TcLevel
-> SkolemInfo
-> [TcTyVar]
-> [TcTyVar]
-> WantedConstraints
-> TcM (Bag Implication, TcEvBinds)
buildImplicationFor TcLevel
tclvl SkolemInfo
skol_info [TcTyVar]
skol_tvs [TcTyVar]
given WantedConstraints
wanted
| WantedConstraints -> Bool
isEmptyWC WantedConstraints
wanted Bool -> Bool -> Bool
&& [TcTyVar] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [TcTyVar]
given
= (Bag Implication, TcEvBinds) -> TcM (Bag Implication, TcEvBinds)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Bag Implication
forall a. Bag a
emptyBag, TcEvBinds
emptyTcEvBinds)
| Bool
otherwise
= ASSERT2( all (isSkolemTyVar <||> isTyVarTyVar) skol_tvs, ppr skol_tvs )
do { EvBindsVar
ev_binds_var <- TcM EvBindsVar
newTcEvBinds
; Implication
implic <- TcM Implication
newImplication
; let implic' :: Implication
implic' = Implication
implic { ic_tclvl :: TcLevel
ic_tclvl = TcLevel
tclvl
, ic_skols :: [TcTyVar]
ic_skols = [TcTyVar]
skol_tvs
, ic_given :: [TcTyVar]
ic_given = [TcTyVar]
given
, ic_wanted :: WantedConstraints
ic_wanted = WantedConstraints
wanted
, ic_binds :: EvBindsVar
ic_binds = EvBindsVar
ev_binds_var
, ic_info :: SkolemInfo
ic_info = SkolemInfo
skol_info }
; (Bag Implication, TcEvBinds) -> TcM (Bag Implication, TcEvBinds)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Implication -> Bag Implication
forall a. a -> Bag a
unitBag Implication
implic', EvBindsVar -> TcEvBinds
TcEvBinds EvBindsVar
ev_binds_var) }
unifyType :: Maybe (HsExpr GhcRn)
-> TcTauType -> TcTauType -> TcM TcCoercionN
unifyType :: Maybe (HsExpr GhcRn) -> TcType -> TcType -> TcM Coercion
unifyType Maybe (HsExpr GhcRn)
thing TcType
ty1 TcType
ty2 = String -> SDoc -> TcRn ()
traceTc String
"utype" (TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty1 SDoc -> SDoc -> SDoc
$$ TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty2 SDoc -> SDoc -> SDoc
$$ Maybe (HsExpr GhcRn) -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable (Maybe a)
External instance of the constraint type forall (p :: Pass).
OutputableBndrId p =>
Outputable (HsExpr (GhcPass p))
External instance of the constraint type OutputableBndr Name
External instance of the constraint type OutputableBndr Name
External instance of the constraint type IsPass 'Renamed
ppr Maybe (HsExpr GhcRn)
thing) TcRn () -> TcM Coercion -> TcM Coercion
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type forall m. Monad (IOEnv m)
>>
TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
TypeLevel CtOrigin
origin TcType
ty1 TcType
ty2
where
origin :: CtOrigin
origin = TypeEqOrigin :: TcType -> TcType -> Maybe SDoc -> Bool -> CtOrigin
TypeEqOrigin { uo_actual :: TcType
uo_actual = TcType
ty1, uo_expected :: TcType
uo_expected = TcType
ty2
, uo_thing :: Maybe SDoc
uo_thing = HsExpr GhcRn -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall (p :: Pass).
OutputableBndrId p =>
Outputable (HsExpr (GhcPass p))
External instance of the constraint type OutputableBndr Name
External instance of the constraint type OutputableBndr Name
External instance of the constraint type IsPass 'Renamed
ppr (HsExpr GhcRn -> SDoc) -> Maybe (HsExpr GhcRn) -> Maybe SDoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
<$> Maybe (HsExpr GhcRn)
thing
, uo_visible :: Bool
uo_visible = Bool
True }
unifyKind :: Maybe (HsType GhcRn) -> TcKind -> TcKind -> TcM CoercionN
unifyKind :: Maybe (HsType GhcRn) -> TcType -> TcType -> TcM Coercion
unifyKind Maybe (HsType GhcRn)
thing TcType
ty1 TcType
ty2 = String -> SDoc -> TcRn ()
traceTc String
"ukind" (TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty1 SDoc -> SDoc -> SDoc
$$ TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty2 SDoc -> SDoc -> SDoc
$$ Maybe (HsType GhcRn) -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable (Maybe a)
External instance of the constraint type forall (p :: Pass).
OutputableBndrId p =>
Outputable (HsType (GhcPass p))
External instance of the constraint type OutputableBndr Name
External instance of the constraint type OutputableBndr Name
External instance of the constraint type IsPass 'Renamed
ppr Maybe (HsType GhcRn)
thing) TcRn () -> TcM Coercion -> TcM Coercion
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type forall m. Monad (IOEnv m)
>>
TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
KindLevel CtOrigin
origin TcType
ty1 TcType
ty2
where origin :: CtOrigin
origin = TypeEqOrigin :: TcType -> TcType -> Maybe SDoc -> Bool -> CtOrigin
TypeEqOrigin { uo_actual :: TcType
uo_actual = TcType
ty1, uo_expected :: TcType
uo_expected = TcType
ty2
, uo_thing :: Maybe SDoc
uo_thing = HsType GhcRn -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall (p :: Pass).
OutputableBndrId p =>
Outputable (HsType (GhcPass p))
External instance of the constraint type OutputableBndr Name
External instance of the constraint type OutputableBndr Name
External instance of the constraint type IsPass 'Renamed
ppr (HsType GhcRn -> SDoc) -> Maybe (HsType GhcRn) -> Maybe SDoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
<$> Maybe (HsType GhcRn)
thing
, uo_visible :: Bool
uo_visible = Bool
True }
uType, uType_defer
:: TypeOrKind
-> CtOrigin
-> TcType
-> TcType
-> TcM CoercionN
uType_defer :: TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType_defer TypeOrKind
t_or_k CtOrigin
origin TcType
ty1 TcType
ty2
= do { Coercion
co <- CtOrigin -> TypeOrKind -> Role -> TcType -> TcType -> TcM Coercion
emitWantedEq CtOrigin
origin TypeOrKind
t_or_k Role
Nominal TcType
ty1 TcType
ty2
; DumpFlag -> TcRn () -> TcRn ()
forall gbl lcl. DumpFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
whenDOptM DumpFlag
Opt_D_dump_tc_trace (TcRn () -> TcRn ()) -> TcRn () -> TcRn ()
forall a b. (a -> b) -> a -> b
$ do
{ [ErrCtxt]
ctxt <- TcM [ErrCtxt]
getErrCtxt
; SDoc
doc <- TidyEnv -> [ErrCtxt] -> TcM SDoc
mkErrInfo TidyEnv
emptyTidyEnv [ErrCtxt]
ctxt
; String -> SDoc -> TcRn ()
traceTc String
"utype_defer" ([SDoc] -> SDoc
vcat [ TcType -> SDoc
debugPprType TcType
ty1
, TcType -> SDoc
debugPprType TcType
ty2
, CtOrigin -> SDoc
pprCtOrigin CtOrigin
origin
, SDoc
doc])
; String -> SDoc -> TcRn ()
traceTc String
"utype_defer2" (Coercion -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Coercion
ppr Coercion
co)
}
; Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return Coercion
co }
uType :: TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
t_or_k CtOrigin
origin TcType
orig_ty1 TcType
orig_ty2
= do { TcLevel
tclvl <- TcM TcLevel
getTcLevel
; String -> SDoc -> TcRn ()
traceTc String
"u_tys" (SDoc -> TcRn ()) -> SDoc -> TcRn ()
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat
[ String -> SDoc
text String
"tclvl" SDoc -> SDoc -> SDoc
<+> TcLevel -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcLevel
ppr TcLevel
tclvl
, [SDoc] -> SDoc
sep [ TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
orig_ty1, String -> SDoc
text String
"~", TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
orig_ty2]
, CtOrigin -> SDoc
pprCtOrigin CtOrigin
origin]
; Coercion
co <- TcType -> TcType -> TcM Coercion
go TcType
orig_ty1 TcType
orig_ty2
; if Coercion -> Bool
isReflCo Coercion
co
then String -> SDoc -> TcRn ()
traceTc String
"u_tys yields no coercion" SDoc
Outputable.empty
else String -> SDoc -> TcRn ()
traceTc String
"u_tys yields coercion:" (Coercion -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Coercion
ppr Coercion
co)
; Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return Coercion
co }
where
go :: TcType -> TcType -> TcM CoercionN
go :: TcType -> TcType -> TcM Coercion
go (CastTy TcType
t1 Coercion
co1) TcType
t2
= do { Coercion
co_tys <- TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
t_or_k CtOrigin
origin TcType
t1 TcType
t2
; Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Role -> TcType -> Coercion -> Coercion -> Coercion
mkCoherenceLeftCo Role
Nominal TcType
t1 Coercion
co1 Coercion
co_tys) }
go TcType
t1 (CastTy TcType
t2 Coercion
co2)
= do { Coercion
co_tys <- TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
t_or_k CtOrigin
origin TcType
t1 TcType
t2
; Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Role -> TcType -> Coercion -> Coercion -> Coercion
mkCoherenceRightCo Role
Nominal TcType
t2 Coercion
co2 Coercion
co_tys) }
go (TyVarTy TcTyVar
tv1) TcType
ty2
= do { LookupTyVarResult
lookup_res <- TcTyVar -> TcM LookupTyVarResult
lookupTcTyVar TcTyVar
tv1
; case LookupTyVarResult
lookup_res of
Filled TcType
ty1 -> do { String -> SDoc -> TcRn ()
traceTc String
"found filled tyvar" (TcTyVar -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcTyVar
ppr TcTyVar
tv1 SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
":->" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty1)
; TcType -> TcType -> TcM Coercion
go TcType
ty1 TcType
ty2 }
Unfilled TcTyVarDetails
_ -> CtOrigin
-> TypeOrKind -> SwapFlag -> TcTyVar -> TcType -> TcM Coercion
uUnfilledVar CtOrigin
origin TypeOrKind
t_or_k SwapFlag
NotSwapped TcTyVar
tv1 TcType
ty2 }
go TcType
ty1 (TyVarTy TcTyVar
tv2)
= do { LookupTyVarResult
lookup_res <- TcTyVar -> TcM LookupTyVarResult
lookupTcTyVar TcTyVar
tv2
; case LookupTyVarResult
lookup_res of
Filled TcType
ty2 -> do { String -> SDoc -> TcRn ()
traceTc String
"found filled tyvar" (TcTyVar -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcTyVar
ppr TcTyVar
tv2 SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
":->" SDoc -> SDoc -> SDoc
<+> TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty2)
; TcType -> TcType -> TcM Coercion
go TcType
ty1 TcType
ty2 }
Unfilled TcTyVarDetails
_ -> CtOrigin
-> TypeOrKind -> SwapFlag -> TcTyVar -> TcType -> TcM Coercion
uUnfilledVar CtOrigin
origin TypeOrKind
t_or_k SwapFlag
IsSwapped TcTyVar
tv2 TcType
ty1 }
go ty1 :: TcType
ty1@(TyConApp TyCon
tc1 []) (TyConApp TyCon
tc2 [])
| TyCon
tc1 TyCon -> TyCon -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq TyCon
== TyCon
tc2
= Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion -> TcM Coercion) -> Coercion -> TcM Coercion
forall a b. (a -> b) -> a -> b
$ TcType -> Coercion
mkNomReflCo TcType
ty1
go TcType
ty1 TcType
ty2
| Just TcType
ty1' <- TcType -> Maybe TcType
tcView TcType
ty1 = TcType -> TcType -> TcM Coercion
go TcType
ty1' TcType
ty2
| Just TcType
ty2' <- TcType -> Maybe TcType
tcView TcType
ty2 = TcType -> TcType -> TcM Coercion
go TcType
ty1 TcType
ty2'
go (FunTy AnonArgFlag
_ TcType
fun1 TcType
arg1) (FunTy AnonArgFlag
_ TcType
fun2 TcType
arg2)
= do { Coercion
co_l <- TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
t_or_k CtOrigin
origin TcType
fun1 TcType
fun2
; Coercion
co_r <- TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
t_or_k CtOrigin
origin TcType
arg1 TcType
arg2
; Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion -> TcM Coercion) -> Coercion -> TcM Coercion
forall a b. (a -> b) -> a -> b
$ Role -> Coercion -> Coercion -> Coercion
mkFunCo Role
Nominal Coercion
co_l Coercion
co_r }
go ty1 :: TcType
ty1@(TyConApp TyCon
tc1 [TcType]
_) TcType
ty2
| TyCon -> Bool
isTypeFamilyTyCon TyCon
tc1 = TcType -> TcType -> TcM Coercion
defer TcType
ty1 TcType
ty2
go TcType
ty1 ty2 :: TcType
ty2@(TyConApp TyCon
tc2 [TcType]
_)
| TyCon -> Bool
isTypeFamilyTyCon TyCon
tc2 = TcType -> TcType -> TcM Coercion
defer TcType
ty1 TcType
ty2
go (TyConApp TyCon
tc1 [TcType]
tys1) (TyConApp TyCon
tc2 [TcType]
tys2)
| TyCon
tc1 TyCon -> TyCon -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq TyCon
== TyCon
tc2, [TcType] -> [TcType] -> Bool
forall a b. [a] -> [b] -> Bool
equalLength [TcType]
tys1 [TcType]
tys2
= ASSERT2( isGenerativeTyCon tc1 Nominal, ppr tc1 )
do { [Coercion]
cos <- (CtOrigin -> TcType -> TcType -> TcM Coercion)
-> [CtOrigin]
-> [TcType]
-> [TcType]
-> IOEnv (Env TcGblEnv TcLclEnv) [Coercion]
forall (m :: * -> *) a b c d.
Monad m =>
(a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m [d]
External instance of the constraint type forall m. Monad (IOEnv m)
zipWith3M (TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
t_or_k) [CtOrigin]
origins' [TcType]
tys1 [TcType]
tys2
; Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion -> TcM Coercion) -> Coercion -> TcM Coercion
forall a b. (a -> b) -> a -> b
$ HasDebugCallStack => Role -> TyCon -> [Coercion] -> Coercion
Role -> TyCon -> [Coercion] -> Coercion
External instance of the constraint type HasDebugCallStack
mkTyConAppCo Role
Nominal TyCon
tc1 [Coercion]
cos }
where
origins' :: [CtOrigin]
origins' = (Bool -> CtOrigin) -> [Bool] -> [CtOrigin]
forall a b. (a -> b) -> [a] -> [b]
map (\Bool
is_vis -> if Bool
is_vis then CtOrigin
origin else CtOrigin -> CtOrigin
toInvisibleOrigin CtOrigin
origin)
(TyCon -> [Bool]
tcTyConVisibilities TyCon
tc1)
go (LitTy TyLit
m) ty :: TcType
ty@(LitTy TyLit
n)
| TyLit
m TyLit -> TyLit -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq TyLit
== TyLit
n
= Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion -> TcM Coercion) -> Coercion -> TcM Coercion
forall a b. (a -> b) -> a -> b
$ TcType -> Coercion
mkNomReflCo TcType
ty
go (AppTy TcType
s1 TcType
t1) (AppTy TcType
s2 TcType
t2)
= Bool -> TcType -> TcType -> TcType -> TcType -> TcM Coercion
go_app (TcType -> Bool
isNextArgVisible TcType
s1) TcType
s1 TcType
t1 TcType
s2 TcType
t2
go (AppTy TcType
s1 TcType
t1) (TyConApp TyCon
tc2 [TcType]
ts2)
| Just ([TcType]
ts2', TcType
t2') <- [TcType] -> Maybe ([TcType], TcType)
forall a. [a] -> Maybe ([a], a)
snocView [TcType]
ts2
= ASSERT( not (mustBeSaturated tc2) )
Bool -> TcType -> TcType -> TcType -> TcType -> TcM Coercion
go_app (TyCon -> [TcType] -> Bool
isNextTyConArgVisible TyCon
tc2 [TcType]
ts2') TcType
s1 TcType
t1 (TyCon -> [TcType] -> TcType
TyConApp TyCon
tc2 [TcType]
ts2') TcType
t2'
go (TyConApp TyCon
tc1 [TcType]
ts1) (AppTy TcType
s2 TcType
t2)
| Just ([TcType]
ts1', TcType
t1') <- [TcType] -> Maybe ([TcType], TcType)
forall a. [a] -> Maybe ([a], a)
snocView [TcType]
ts1
= ASSERT( not (mustBeSaturated tc1) )
Bool -> TcType -> TcType -> TcType -> TcType -> TcM Coercion
go_app (TyCon -> [TcType] -> Bool
isNextTyConArgVisible TyCon
tc1 [TcType]
ts1') (TyCon -> [TcType] -> TcType
TyConApp TyCon
tc1 [TcType]
ts1') TcType
t1' TcType
s2 TcType
t2
go (CoercionTy Coercion
co1) (CoercionTy Coercion
co2)
= do { let ty1 :: TcType
ty1 = Coercion -> TcType
coercionType Coercion
co1
ty2 :: TcType
ty2 = Coercion -> TcType
coercionType Coercion
co2
; Coercion
kco <- TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
KindLevel
(TcType -> Maybe TcType -> CtOrigin -> Maybe TypeOrKind -> CtOrigin
KindEqOrigin TcType
orig_ty1 (TcType -> Maybe TcType
forall a. a -> Maybe a
Just TcType
orig_ty2) CtOrigin
origin
(TypeOrKind -> Maybe TypeOrKind
forall a. a -> Maybe a
Just TypeOrKind
t_or_k))
TcType
ty1 TcType
ty2
; Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion -> TcM Coercion) -> Coercion -> TcM Coercion
forall a b. (a -> b) -> a -> b
$ Role -> Coercion -> Coercion -> Coercion -> Coercion
mkProofIrrelCo Role
Nominal Coercion
kco Coercion
co1 Coercion
co2 }
go TcType
ty1 TcType
ty2 = TcType -> TcType -> TcM Coercion
defer TcType
ty1 TcType
ty2
defer :: TcType -> TcType -> TcM Coercion
defer TcType
ty1 TcType
ty2
| TcType
ty1 HasDebugCallStack => TcType -> TcType -> Bool
TcType -> TcType -> Bool
External instance of the constraint type HasDebugCallStack
`tcEqType` TcType
ty2 = Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcType -> Coercion
mkNomReflCo TcType
ty1)
| Bool
otherwise = TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType_defer TypeOrKind
t_or_k CtOrigin
origin TcType
ty1 TcType
ty2
go_app :: Bool -> TcType -> TcType -> TcType -> TcType -> TcM Coercion
go_app Bool
vis TcType
s1 TcType
t1 TcType
s2 TcType
t2
= do { Coercion
co_s <- TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
t_or_k CtOrigin
origin TcType
s1 TcType
s2
; let arg_origin :: CtOrigin
arg_origin
| Bool
vis = CtOrigin
origin
| Bool
otherwise = CtOrigin -> CtOrigin
toInvisibleOrigin CtOrigin
origin
; Coercion
co_t <- TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
t_or_k CtOrigin
arg_origin TcType
t1 TcType
t2
; Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion -> TcM Coercion) -> Coercion -> TcM Coercion
forall a b. (a -> b) -> a -> b
$ Coercion -> Coercion -> Coercion
mkAppCo Coercion
co_s Coercion
co_t }
uUnfilledVar :: CtOrigin
-> TypeOrKind
-> SwapFlag
-> TcTyVar
-> TcTauType
-> TcM Coercion
uUnfilledVar :: CtOrigin
-> TypeOrKind -> SwapFlag -> TcTyVar -> TcType -> TcM Coercion
uUnfilledVar CtOrigin
origin TypeOrKind
t_or_k SwapFlag
swapped TcTyVar
tv1 TcType
ty2
= do { TcType
ty2 <- TcType -> IOEnv (Env TcGblEnv TcLclEnv) TcType
zonkTcType TcType
ty2
; CtOrigin
-> TypeOrKind -> SwapFlag -> TcTyVar -> TcType -> TcM Coercion
uUnfilledVar1 CtOrigin
origin TypeOrKind
t_or_k SwapFlag
swapped TcTyVar
tv1 TcType
ty2 }
uUnfilledVar1 :: CtOrigin
-> TypeOrKind
-> SwapFlag
-> TcTyVar
-> TcTauType
-> TcM Coercion
uUnfilledVar1 :: CtOrigin
-> TypeOrKind -> SwapFlag -> TcTyVar -> TcType -> TcM Coercion
uUnfilledVar1 CtOrigin
origin TypeOrKind
t_or_k SwapFlag
swapped TcTyVar
tv1 TcType
ty2
| Just TcTyVar
tv2 <- TcType -> Maybe TcTyVar
tcGetTyVar_maybe TcType
ty2
= TcTyVar -> TcM Coercion
go TcTyVar
tv2
| Bool
otherwise
= CtOrigin
-> TypeOrKind -> SwapFlag -> TcTyVar -> TcType -> TcM Coercion
uUnfilledVar2 CtOrigin
origin TypeOrKind
t_or_k SwapFlag
swapped TcTyVar
tv1 TcType
ty2
where
go :: TcTyVar -> TcM Coercion
go TcTyVar
tv2 | TcTyVar
tv1 TcTyVar -> TcTyVar -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq TcTyVar
== TcTyVar
tv2
= Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcType -> Coercion
mkNomReflCo (TcTyVar -> TcType
mkTyVarTy TcTyVar
tv1))
| TcTyVar -> TcTyVar -> Bool
swapOverTyVars TcTyVar
tv1 TcTyVar
tv2
= do { TcTyVar
tv1 <- TcTyVar -> TcM TcTyVar
zonkTyCoVarKind TcTyVar
tv1
; CtOrigin
-> TypeOrKind -> SwapFlag -> TcTyVar -> TcType -> TcM Coercion
uUnfilledVar2 CtOrigin
origin TypeOrKind
t_or_k (SwapFlag -> SwapFlag
flipSwap SwapFlag
swapped)
TcTyVar
tv2 (TcTyVar -> TcType
mkTyVarTy TcTyVar
tv1) }
| Bool
otherwise
= CtOrigin
-> TypeOrKind -> SwapFlag -> TcTyVar -> TcType -> TcM Coercion
uUnfilledVar2 CtOrigin
origin TypeOrKind
t_or_k SwapFlag
swapped TcTyVar
tv1 TcType
ty2
uUnfilledVar2 :: CtOrigin
-> TypeOrKind
-> SwapFlag
-> TcTyVar
-> TcTauType
-> TcM Coercion
uUnfilledVar2 :: CtOrigin
-> TypeOrKind -> SwapFlag -> TcTyVar -> TcType -> TcM Coercion
uUnfilledVar2 CtOrigin
origin TypeOrKind
t_or_k SwapFlag
swapped TcTyVar
tv1 TcType
ty2
= do { DynFlags
dflags <- IOEnv (Env TcGblEnv TcLclEnv) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type forall env. ContainsDynFlags env => HasDynFlags (IOEnv env)
External instance of the constraint type forall gbl lcl. ContainsDynFlags (Env gbl lcl)
getDynFlags
; TcLevel
cur_lvl <- TcM TcLevel
getTcLevel
; DynFlags -> TcLevel -> TcM Coercion
go DynFlags
dflags TcLevel
cur_lvl }
where
go :: DynFlags -> TcLevel -> TcM Coercion
go DynFlags
dflags TcLevel
cur_lvl
| TcLevel -> TcTyVar -> TcType -> Bool
canSolveByUnification TcLevel
cur_lvl TcTyVar
tv1 TcType
ty2
, MTVU_OK TcType
ty2' <- DynFlags -> TcTyVar -> TcType -> MetaTyVarUpdateResult TcType
metaTyVarUpdateOK DynFlags
dflags TcTyVar
tv1 TcType
ty2
= do { Coercion
co_k <- TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
KindLevel CtOrigin
kind_origin (HasDebugCallStack => TcType -> TcType
TcType -> TcType
External instance of the constraint type HasDebugCallStack
tcTypeKind TcType
ty2') (TcTyVar -> TcType
tyVarKind TcTyVar
tv1)
; String -> SDoc -> TcRn ()
traceTc String
"uUnfilledVar2 ok" (SDoc -> TcRn ()) -> SDoc -> TcRn ()
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat [ TcTyVar -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcTyVar
ppr TcTyVar
tv1 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 (TcTyVar -> TcType
tyVarKind TcTyVar
tv1)
, TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty2 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 (HasDebugCallStack => TcType -> TcType
TcType -> TcType
External instance of the constraint type HasDebugCallStack
tcTypeKind TcType
ty2)
, Bool -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Bool
ppr (Coercion -> Bool
isTcReflCo Coercion
co_k), Coercion -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Coercion
ppr Coercion
co_k ]
; if Coercion -> Bool
isTcReflCo Coercion
co_k
then do { TcTyVar -> TcType -> TcRn ()
writeMetaTyVar TcTyVar
tv1 TcType
ty2'
; Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcType -> Coercion
mkTcNomReflCo TcType
ty2') }
else TcM Coercion
defer }
| Bool
otherwise
= do { String -> SDoc -> TcRn ()
traceTc String
"uUnfilledVar2 not ok" (TcTyVar -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcTyVar
ppr TcTyVar
tv1 SDoc -> SDoc -> SDoc
$$ TcType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TcType
ppr TcType
ty2)
; TcM Coercion
defer }
ty1 :: TcType
ty1 = TcTyVar -> TcType
mkTyVarTy TcTyVar
tv1
kind_origin :: CtOrigin
kind_origin = TcType -> Maybe TcType -> CtOrigin -> Maybe TypeOrKind -> CtOrigin
KindEqOrigin TcType
ty1 (TcType -> Maybe TcType
forall a. a -> Maybe a
Just TcType
ty2) CtOrigin
origin (TypeOrKind -> Maybe TypeOrKind
forall a. a -> Maybe a
Just TypeOrKind
t_or_k)
defer :: TcM Coercion
defer = SwapFlag
-> (TcType -> TcType -> TcM Coercion)
-> TcType
-> TcType
-> TcM Coercion
forall a b. SwapFlag -> (a -> a -> b) -> a -> a -> b
unSwap SwapFlag
swapped (TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType_defer TypeOrKind
t_or_k CtOrigin
origin) TcType
ty1 TcType
ty2
swapOverTyVars :: TcTyVar -> TcTyVar -> Bool
swapOverTyVars :: TcTyVar -> TcTyVar -> Bool
swapOverTyVars TcTyVar
tv1 TcTyVar
tv2
| TcLevel
lvl1 TcLevel -> TcLevel -> Bool
`strictlyDeeperThan` TcLevel
lvl2 = Bool
False
| TcLevel
lvl2 TcLevel -> TcLevel -> Bool
`strictlyDeeperThan` TcLevel
lvl1 = Bool
True
| Int
pri1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
pri2 = Bool
False
| Int
pri2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
pri1 = Bool
True
| Name -> Bool
isSystemName Name
tv2_name, Bool -> Bool
not (Name -> Bool
isSystemName Name
tv1_name) = Bool
True
| Bool
otherwise = Bool
False
where
lvl1 :: TcLevel
lvl1 = TcTyVar -> TcLevel
tcTyVarLevel TcTyVar
tv1
lvl2 :: TcLevel
lvl2 = TcTyVar -> TcLevel
tcTyVarLevel TcTyVar
tv2
pri1 :: Int
pri1 = TcTyVar -> Int
lhsPriority TcTyVar
tv1
pri2 :: Int
pri2 = TcTyVar -> Int
lhsPriority TcTyVar
tv2
tv1_name :: Name
tv1_name = TcTyVar -> Name
Var.varName TcTyVar
tv1
tv2_name :: Name
tv2_name = TcTyVar -> Name
Var.varName TcTyVar
tv2
lhsPriority :: TcTyVar -> Int
lhsPriority :: TcTyVar -> Int
lhsPriority TcTyVar
tv
= ASSERT2( isTyVar tv, ppr tv)
case TcTyVar -> TcTyVarDetails
tcTyVarDetails TcTyVar
tv of
TcTyVarDetails
RuntimeUnk -> Int
0
SkolemTv {} -> Int
0
MetaTv { mtv_info :: TcTyVarDetails -> MetaInfo
mtv_info = MetaInfo
info } -> case MetaInfo
info of
MetaInfo
FlatSkolTv -> Int
1
MetaInfo
TyVarTv -> Int
2
MetaInfo
TauTv -> Int
3
MetaInfo
FlatMetaTv -> Int
4
canSolveByUnification :: TcLevel -> TcTyVar -> TcType -> Bool
canSolveByUnification :: TcLevel -> TcTyVar -> TcType -> Bool
canSolveByUnification TcLevel
tclvl TcTyVar
tv TcType
xi
| TcLevel -> TcTyVar -> Bool
isTouchableMetaTyVar TcLevel
tclvl TcTyVar
tv
= case TcTyVar -> MetaInfo
metaTyVarInfo TcTyVar
tv of
MetaInfo
TyVarTv -> TcType -> Bool
is_tyvar TcType
xi
MetaInfo
_ -> Bool
True
| Bool
otherwise
= Bool
False
where
is_tyvar :: TcType -> Bool
is_tyvar TcType
xi
= case TcType -> Maybe TcTyVar
tcGetTyVar_maybe TcType
xi of
Maybe TcTyVar
Nothing -> Bool
False
Just TcTyVar
tv -> case TcTyVar -> TcTyVarDetails
tcTyVarDetails TcTyVar
tv of
MetaTv { mtv_info :: TcTyVarDetails -> MetaInfo
mtv_info = MetaInfo
info }
-> case MetaInfo
info of
MetaInfo
TyVarTv -> Bool
True
MetaInfo
_ -> Bool
False
SkolemTv {} -> Bool
True
TcTyVarDetails
RuntimeUnk -> Bool
True
data LookupTyVarResult
= Unfilled TcTyVarDetails
| Filled TcType
lookupTcTyVar :: TcTyVar -> TcM LookupTyVarResult
lookupTcTyVar :: TcTyVar -> TcM LookupTyVarResult
lookupTcTyVar TcTyVar
tyvar
| MetaTv { mtv_ref :: TcTyVarDetails -> IORef MetaDetails
mtv_ref = IORef MetaDetails
ref } <- TcTyVarDetails
details
= do { MetaDetails
meta_details <- IORef MetaDetails -> TcM MetaDetails
forall a env. IORef a -> IOEnv env a
readMutVar IORef MetaDetails
ref
; case MetaDetails
meta_details of
Indirect TcType
ty -> LookupTyVarResult -> TcM LookupTyVarResult
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcType -> LookupTyVarResult
Filled TcType
ty)
MetaDetails
Flexi -> do { Bool
is_touchable <- TcTyVar -> TcM Bool
isTouchableTcM TcTyVar
tyvar
; if Bool
is_touchable then
LookupTyVarResult -> TcM LookupTyVarResult
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcTyVarDetails -> LookupTyVarResult
Unfilled TcTyVarDetails
details)
else
LookupTyVarResult -> TcM LookupTyVarResult
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcTyVarDetails -> LookupTyVarResult
Unfilled TcTyVarDetails
vanillaSkolemTv) } }
| Bool
otherwise
= LookupTyVarResult -> TcM LookupTyVarResult
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcTyVarDetails -> LookupTyVarResult
Unfilled TcTyVarDetails
details)
where
details :: TcTyVarDetails
details = TcTyVar -> TcTyVarDetails
tcTyVarDetails TcTyVar
tyvar
matchExpectedFunKind
:: Outputable fun
=> fun
-> Arity
-> TcKind
-> TcM Coercion
matchExpectedFunKind :: fun -> Int -> TcType -> TcM Coercion
matchExpectedFunKind fun
hs_ty Int
n TcType
k = Int -> TcType -> TcM Coercion
go Int
n TcType
k
where
go :: Int -> TcType -> TcM Coercion
go Int
0 TcType
k = Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcType -> Coercion
mkNomReflCo TcType
k)
go Int
n TcType
k | Just TcType
k' <- TcType -> Maybe TcType
tcView TcType
k = Int -> TcType -> TcM Coercion
go Int
n TcType
k'
go Int
n k :: TcType
k@(TyVarTy TcTyVar
kvar)
| TcTyVar -> Bool
isMetaTyVar TcTyVar
kvar
= do { MetaDetails
maybe_kind <- TcTyVar -> TcM MetaDetails
readMetaTyVar TcTyVar
kvar
; case MetaDetails
maybe_kind of
Indirect TcType
fun_kind -> Int -> TcType -> TcM Coercion
go Int
n TcType
fun_kind
MetaDetails
Flexi -> Int -> TcType -> TcM Coercion
defer Int
n TcType
k }
go Int
n (FunTy AnonArgFlag
_ TcType
arg TcType
res)
= do { Coercion
co <- Int -> TcType -> TcM Coercion
go (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
-Int
1) TcType
res
; Coercion -> TcM Coercion
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Role -> Coercion -> Coercion -> Coercion
mkTcFunCo Role
Nominal (TcType -> Coercion
mkTcNomReflCo TcType
arg) Coercion
co) }
go Int
n TcType
other
= Int -> TcType -> TcM Coercion
defer Int
n TcType
other
defer :: Int -> TcType -> TcM Coercion
defer Int
n TcType
k
= do { [TcType]
arg_kinds <- Int -> IOEnv (Env TcGblEnv TcLclEnv) [TcType]
newMetaKindVars Int
n
; TcType
res_kind <- IOEnv (Env TcGblEnv TcLclEnv) TcType
newMetaKindVar
; let new_fun :: TcType
new_fun = [TcType] -> TcType -> TcType
mkVisFunTys [TcType]
arg_kinds TcType
res_kind
origin :: CtOrigin
origin = TypeEqOrigin :: TcType -> TcType -> Maybe SDoc -> Bool -> CtOrigin
TypeEqOrigin { uo_actual :: TcType
uo_actual = TcType
k
, uo_expected :: TcType
uo_expected = TcType
new_fun
, uo_thing :: Maybe SDoc
uo_thing = SDoc -> Maybe SDoc
forall a. a -> Maybe a
Just (fun -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable fun
ppr fun
hs_ty)
, uo_visible :: Bool
uo_visible = Bool
True
}
; TypeOrKind -> CtOrigin -> TcType -> TcType -> TcM Coercion
uType TypeOrKind
KindLevel CtOrigin
origin TcType
k TcType
new_fun }
data MetaTyVarUpdateResult a
= MTVU_OK a
| MTVU_Bad
| MTVU_HoleBlocker
| MTVU_Occurs
deriving (a -> MetaTyVarUpdateResult b -> MetaTyVarUpdateResult a
(a -> b) -> MetaTyVarUpdateResult a -> MetaTyVarUpdateResult b
(forall a b.
(a -> b) -> MetaTyVarUpdateResult a -> MetaTyVarUpdateResult b)
-> (forall a b.
a -> MetaTyVarUpdateResult b -> MetaTyVarUpdateResult a)
-> Functor MetaTyVarUpdateResult
forall a b. a -> MetaTyVarUpdateResult b -> MetaTyVarUpdateResult a
forall a b.
(a -> b) -> MetaTyVarUpdateResult a -> MetaTyVarUpdateResult b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> MetaTyVarUpdateResult b -> MetaTyVarUpdateResult a
$c<$ :: forall a b. a -> MetaTyVarUpdateResult b -> MetaTyVarUpdateResult a
fmap :: (a -> b) -> MetaTyVarUpdateResult a -> MetaTyVarUpdateResult b
$cfmap :: forall a b.
(a -> b) -> MetaTyVarUpdateResult a -> MetaTyVarUpdateResult b
Functor)
instance Applicative MetaTyVarUpdateResult where
pure :: a -> MetaTyVarUpdateResult a
pure = a -> MetaTyVarUpdateResult a
forall a. a -> MetaTyVarUpdateResult a
MTVU_OK
<*> :: MetaTyVarUpdateResult (a -> b)
-> MetaTyVarUpdateResult a -> MetaTyVarUpdateResult b
(<*>) = MetaTyVarUpdateResult (a -> b)
-> MetaTyVarUpdateResult a -> MetaTyVarUpdateResult b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
Instance of class: Monad of the constraint type Monad MetaTyVarUpdateResult
ap
instance Monad MetaTyVarUpdateResult where
MTVU_OK a
x >>= :: MetaTyVarUpdateResult a
-> (a -> MetaTyVarUpdateResult b) -> MetaTyVarUpdateResult b
>>= a -> MetaTyVarUpdateResult b
k = a -> MetaTyVarUpdateResult b
k a
x
MetaTyVarUpdateResult a
MTVU_Bad >>= a -> MetaTyVarUpdateResult b
_ = MetaTyVarUpdateResult b
forall a. MetaTyVarUpdateResult a
MTVU_Bad
MetaTyVarUpdateResult a
MTVU_HoleBlocker >>= a -> MetaTyVarUpdateResult b
_ = MetaTyVarUpdateResult b
forall a. MetaTyVarUpdateResult a
MTVU_HoleBlocker
MetaTyVarUpdateResult a
MTVU_Occurs >>= a -> MetaTyVarUpdateResult b
_ = MetaTyVarUpdateResult b
forall a. MetaTyVarUpdateResult a
MTVU_Occurs
instance Outputable a => Outputable (MetaTyVarUpdateResult a) where
ppr :: MetaTyVarUpdateResult a -> SDoc
ppr (MTVU_OK a
a) = String -> SDoc
text String
"MTVU_OK" SDoc -> SDoc -> SDoc
<+> a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
a
ppr MetaTyVarUpdateResult a
MTVU_Bad = String -> SDoc
text String
"MTVU_Bad"
ppr MetaTyVarUpdateResult a
MTVU_HoleBlocker = String -> SDoc
text String
"MTVU_HoleBlocker"
ppr MetaTyVarUpdateResult a
MTVU_Occurs = String -> SDoc
text String
"MTVU_Occurs"
occCheckForErrors :: DynFlags -> TcTyVar -> Type -> MetaTyVarUpdateResult ()
occCheckForErrors :: DynFlags -> TcTyVar -> TcType -> MetaTyVarUpdateResult ()
occCheckForErrors DynFlags
dflags TcTyVar
tv TcType
ty
= case DynFlags -> Bool -> TcTyVar -> TcType -> MetaTyVarUpdateResult ()
preCheck DynFlags
dflags Bool
True TcTyVar
tv TcType
ty of
MTVU_OK ()
_ -> () -> MetaTyVarUpdateResult ()
forall a. a -> MetaTyVarUpdateResult a
MTVU_OK ()
MetaTyVarUpdateResult ()
MTVU_Bad -> MetaTyVarUpdateResult ()
forall a. MetaTyVarUpdateResult a
MTVU_Bad
MetaTyVarUpdateResult ()
MTVU_HoleBlocker -> MetaTyVarUpdateResult ()
forall a. MetaTyVarUpdateResult a
MTVU_HoleBlocker
MetaTyVarUpdateResult ()
MTVU_Occurs -> case [TcTyVar] -> TcType -> Maybe TcType
occCheckExpand [TcTyVar
tv] TcType
ty of
Maybe TcType
Nothing -> MetaTyVarUpdateResult ()
forall a. MetaTyVarUpdateResult a
MTVU_Occurs
Just TcType
_ -> () -> MetaTyVarUpdateResult ()
forall a. a -> MetaTyVarUpdateResult a
MTVU_OK ()
metaTyVarUpdateOK :: DynFlags
-> TcTyVar
-> TcType
-> MetaTyVarUpdateResult TcType
metaTyVarUpdateOK :: DynFlags -> TcTyVar -> TcType -> MetaTyVarUpdateResult TcType
metaTyVarUpdateOK DynFlags
dflags TcTyVar
tv TcType
ty
= case DynFlags -> Bool -> TcTyVar -> TcType -> MetaTyVarUpdateResult ()
preCheck DynFlags
dflags Bool
False TcTyVar
tv TcType
ty of
MTVU_OK ()
_ -> TcType -> MetaTyVarUpdateResult TcType
forall a. a -> MetaTyVarUpdateResult a
MTVU_OK TcType
ty
MetaTyVarUpdateResult ()
MTVU_Bad -> MetaTyVarUpdateResult TcType
forall a. MetaTyVarUpdateResult a
MTVU_Bad
MetaTyVarUpdateResult ()
MTVU_HoleBlocker -> MetaTyVarUpdateResult TcType
forall a. MetaTyVarUpdateResult a
MTVU_HoleBlocker
MetaTyVarUpdateResult ()
MTVU_Occurs -> case [TcTyVar] -> TcType -> Maybe TcType
occCheckExpand [TcTyVar
tv] TcType
ty of
Just TcType
expanded_ty -> TcType -> MetaTyVarUpdateResult TcType
forall a. a -> MetaTyVarUpdateResult a
MTVU_OK TcType
expanded_ty
Maybe TcType
Nothing -> MetaTyVarUpdateResult TcType
forall a. MetaTyVarUpdateResult a
MTVU_Occurs
preCheck :: DynFlags -> Bool -> TcTyVar -> TcType -> MetaTyVarUpdateResult ()
preCheck :: DynFlags -> Bool -> TcTyVar -> TcType -> MetaTyVarUpdateResult ()
preCheck DynFlags
dflags Bool
ty_fam_ok TcTyVar
tv TcType
ty
= TcType -> MetaTyVarUpdateResult ()
fast_check TcType
ty
where
details :: TcTyVarDetails
details = TcTyVar -> TcTyVarDetails
tcTyVarDetails TcTyVar
tv
impredicative_ok :: Bool
impredicative_ok = DynFlags -> TcTyVarDetails -> Bool
canUnifyWithPolyType DynFlags
dflags TcTyVarDetails
details
ok :: MetaTyVarUpdateResult ()
ok :: MetaTyVarUpdateResult ()
ok = () -> MetaTyVarUpdateResult ()
forall a. a -> MetaTyVarUpdateResult a
MTVU_OK ()
fast_check :: TcType -> MetaTyVarUpdateResult ()
fast_check :: TcType -> MetaTyVarUpdateResult ()
fast_check (TyVarTy TcTyVar
tv')
| TcTyVar
tv TcTyVar -> TcTyVar -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq TcTyVar
== TcTyVar
tv' = MetaTyVarUpdateResult ()
forall a. MetaTyVarUpdateResult a
MTVU_Occurs
| Bool
otherwise = TcType -> MetaTyVarUpdateResult ()
fast_check_occ (TcTyVar -> TcType
tyVarKind TcTyVar
tv')
fast_check (TyConApp TyCon
tc [TcType]
tys)
| TyCon -> Bool
bad_tc TyCon
tc = MetaTyVarUpdateResult ()
forall a. MetaTyVarUpdateResult a
MTVU_Bad
| Bool
otherwise = (TcType -> MetaTyVarUpdateResult ())
-> [TcType] -> MetaTyVarUpdateResult [()]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
Instance of class: Monad of the constraint type Monad MetaTyVarUpdateResult
External instance of the constraint type Traversable []
mapM TcType -> MetaTyVarUpdateResult ()
fast_check [TcType]
tys MetaTyVarUpdateResult [()]
-> MetaTyVarUpdateResult () -> MetaTyVarUpdateResult ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
Instance of class: Monad of the constraint type Monad MetaTyVarUpdateResult
>> MetaTyVarUpdateResult ()
ok
fast_check (LitTy {}) = MetaTyVarUpdateResult ()
ok
fast_check (FunTy{ft_af :: TcType -> AnonArgFlag
ft_af = AnonArgFlag
af, ft_arg :: TcType -> TcType
ft_arg = TcType
a, ft_res :: TcType -> TcType
ft_res = TcType
r})
| AnonArgFlag
InvisArg <- AnonArgFlag
af
, Bool -> Bool
not Bool
impredicative_ok = MetaTyVarUpdateResult ()
forall a. MetaTyVarUpdateResult a
MTVU_Bad
| Bool
otherwise = TcType -> MetaTyVarUpdateResult ()
fast_check TcType
a MetaTyVarUpdateResult ()
-> MetaTyVarUpdateResult () -> MetaTyVarUpdateResult ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
Instance of class: Monad of the constraint type Monad MetaTyVarUpdateResult
>> TcType -> MetaTyVarUpdateResult ()
fast_check TcType
r
fast_check (AppTy TcType
fun TcType
arg) = TcType -> MetaTyVarUpdateResult ()
fast_check TcType
fun MetaTyVarUpdateResult ()
-> MetaTyVarUpdateResult () -> MetaTyVarUpdateResult ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
Instance of class: Monad of the constraint type Monad MetaTyVarUpdateResult
>> TcType -> MetaTyVarUpdateResult ()
fast_check TcType
arg
fast_check (CastTy TcType
ty Coercion
co) = TcType -> MetaTyVarUpdateResult ()
fast_check TcType
ty MetaTyVarUpdateResult ()
-> MetaTyVarUpdateResult () -> MetaTyVarUpdateResult ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
Instance of class: Monad of the constraint type Monad MetaTyVarUpdateResult
>> Coercion -> MetaTyVarUpdateResult ()
fast_check_co Coercion
co
fast_check (CoercionTy Coercion
co) = Coercion -> MetaTyVarUpdateResult ()
fast_check_co Coercion
co
fast_check (ForAllTy (Bndr TcTyVar
tv' ArgFlag
_) TcType
ty)
| Bool -> Bool
not Bool
impredicative_ok = MetaTyVarUpdateResult ()
forall a. MetaTyVarUpdateResult a
MTVU_Bad
| TcTyVar
tv TcTyVar -> TcTyVar -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq TcTyVar
== TcTyVar
tv' = MetaTyVarUpdateResult ()
ok
| Bool
otherwise = do { TcType -> MetaTyVarUpdateResult ()
fast_check_occ (TcTyVar -> TcType
tyVarKind TcTyVar
tv')
; TcType -> MetaTyVarUpdateResult ()
fast_check_occ TcType
ty }
fast_check_occ :: TcType -> MetaTyVarUpdateResult ()
fast_check_occ TcType
k | TcTyVar
tv TcTyVar -> VarSet -> Bool
`elemVarSet` TcType -> VarSet
tyCoVarsOfType TcType
k = MetaTyVarUpdateResult ()
forall a. MetaTyVarUpdateResult a
MTVU_Occurs
| Bool
otherwise = MetaTyVarUpdateResult ()
ok
fast_check_co :: Coercion -> MetaTyVarUpdateResult ()
fast_check_co Coercion
co | Bool -> Bool
not (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_DeferTypeErrors DynFlags
dflags)
, Coercion -> Bool
badCoercionHoleCo Coercion
co = MetaTyVarUpdateResult ()
forall a. MetaTyVarUpdateResult a
MTVU_HoleBlocker
| TcTyVar
tv TcTyVar -> VarSet -> Bool
`elemVarSet` Coercion -> VarSet
tyCoVarsOfCo Coercion
co = MetaTyVarUpdateResult ()
forall a. MetaTyVarUpdateResult a
MTVU_Occurs
| Bool
otherwise = MetaTyVarUpdateResult ()
ok
bad_tc :: TyCon -> Bool
bad_tc :: TyCon -> Bool
bad_tc TyCon
tc
| Bool -> Bool
not (Bool
impredicative_ok Bool -> Bool -> Bool
|| TyCon -> Bool
isTauTyCon TyCon
tc) = Bool
True
| Bool -> Bool
not (Bool
ty_fam_ok Bool -> Bool -> Bool
|| TyCon -> Bool
isFamFreeTyCon TyCon
tc) = Bool
True
| Bool
otherwise = Bool
False
canUnifyWithPolyType :: DynFlags -> TcTyVarDetails -> Bool
canUnifyWithPolyType :: DynFlags -> TcTyVarDetails -> Bool
canUnifyWithPolyType DynFlags
dflags TcTyVarDetails
details
= case TcTyVarDetails
details of
MetaTv { mtv_info :: TcTyVarDetails -> MetaInfo
mtv_info = MetaInfo
TyVarTv } -> Bool
False
MetaTv { mtv_info :: TcTyVarDetails -> MetaInfo
mtv_info = MetaInfo
TauTv } -> Extension -> DynFlags -> Bool
xopt Extension
LangExt.ImpredicativeTypes DynFlags
dflags
TcTyVarDetails
_other -> Bool
True