{-# LANGUAGE CPP, MultiWayIf, TupleSections #-}
{-# LANGUAGE FlexibleContexts #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
module GHC.Tc.Utils.Instantiate (
deeplySkolemise,
topInstantiate, topInstantiateInferred, deeplyInstantiate,
instCall, instDFunType, instStupidTheta, instTyVarsWith,
newWanted, newWanteds,
tcInstInvisibleTyBinders, tcInstInvisibleTyBinder,
newOverloadedLit, mkOverLit,
newClsInst,
tcGetInsts, tcGetInstEnvs, getOverlapFlag,
tcExtendLocalInstEnv,
instCallConstraints, newMethodFromName,
tcSyntaxName,
tyCoVarsOfWC,
tyCoVarsOfCt, tyCoVarsOfCts,
) where
#include "HsVersions.h"
import GHC.Prelude
import {-# SOURCE #-} GHC.Tc.Gen.Expr( tcCheckExpr, tcSyntaxOp )
import {-# SOURCE #-} GHC.Tc.Utils.Unify( unifyType, unifyKind )
import GHC.Types.Basic ( IntegralLit(..), SourceText(..) )
import GHC.Data.FastString
import GHC.Hs
import GHC.Tc.Utils.Zonk
import GHC.Tc.Utils.Monad
import GHC.Tc.Types.Constraint
import GHC.Core.Predicate
import GHC.Tc.Types.Origin
import GHC.Tc.Utils.Env
import GHC.Tc.Types.Evidence
import GHC.Core.InstEnv
import GHC.Builtin.Types ( heqDataCon, eqDataCon )
import GHC.Core ( isOrphan )
import GHC.Tc.Instance.FunDeps
import GHC.Tc.Utils.TcMType
import GHC.Core.Type
import GHC.Core.TyCo.Rep
import GHC.Core.TyCo.Ppr ( debugPprType )
import GHC.Tc.Utils.TcType
import GHC.Driver.Types
import GHC.Core.Class( Class )
import GHC.Types.Id.Make( mkDictFunId )
import GHC.Core( Expr(..) )
import GHC.Types.Id
import GHC.Types.Name
import GHC.Types.Var ( EvVar, tyVarName, VarBndr(..) )
import GHC.Core.DataCon
import GHC.Types.Var.Env
import GHC.Builtin.Names
import GHC.Types.SrcLoc as SrcLoc
import GHC.Driver.Session
import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Types.Basic ( TypeOrKind(..) )
import qualified GHC.LanguageExtensions as LangExt
import Data.List ( sortBy )
import Control.Monad( unless )
import Data.Function ( on )
newMethodFromName
:: CtOrigin
-> Name
-> [TcRhoType]
-> TcM (HsExpr GhcTcId)
newMethodFromName :: CtOrigin -> Name -> ThetaType -> TcM (HsExpr GhcTcId)
newMethodFromName CtOrigin
origin Name
name ThetaType
ty_args
= do { DFunId
id <- Name -> TcM DFunId
tcLookupId Name
name
; let ty :: Type
ty = HasDebugCallStack => Type -> ThetaType -> Type
Type -> ThetaType -> Type
External instance of the constraint type HasDebugCallStack
piResultTys (DFunId -> Type
idType DFunId
id) ThetaType
ty_args
(ThetaType
theta, Type
_caller_knows_this) = Type -> (ThetaType, Type)
tcSplitPhiTy Type
ty
; HsWrapper
wrap <- ASSERT( not (isForAllTy ty) && isSingleton theta )
CtOrigin
-> ThetaType
-> ThetaType
-> IOEnv (Env TcGblEnv TcLclEnv) HsWrapper
instCall CtOrigin
origin ThetaType
ty_args ThetaType
theta
; 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
wrap (XVar GhcTcId -> Located (IdP GhcTcId) -> HsExpr GhcTcId
forall p. XVar p -> Located (IdP p) -> HsExpr p
HsVar XVar GhcTcId
NoExtField
noExtField (DFunId -> Located DFunId
forall e. e -> Located e
noLoc DFunId
id))) }
deeplySkolemise :: TcSigmaType
-> TcM ( HsWrapper
, [(Name,TyVar)]
, [EvVar]
, TcRhoType )
deeplySkolemise :: Type -> TcM (HsWrapper, [(Name, DFunId)], [DFunId], Type)
deeplySkolemise Type
ty
= TCvSubst
-> Type -> TcM (HsWrapper, [(Name, DFunId)], [DFunId], Type)
go TCvSubst
init_subst Type
ty
where
init_subst :: TCvSubst
init_subst = InScopeSet -> TCvSubst
mkEmptyTCvSubst (VarSet -> InScopeSet
mkInScopeSet (Type -> VarSet
tyCoVarsOfType Type
ty))
go :: TCvSubst
-> Type -> TcM (HsWrapper, [(Name, DFunId)], [DFunId], Type)
go TCvSubst
subst Type
ty
| Just (ThetaType
arg_tys, [DFunId]
tvs, ThetaType
theta, Type
ty') <- Type -> Maybe (ThetaType, [DFunId], ThetaType, Type)
tcDeepSplitSigmaTy_maybe Type
ty
= do { let arg_tys' :: ThetaType
arg_tys' = HasCallStack => TCvSubst -> ThetaType -> ThetaType
TCvSubst -> ThetaType -> ThetaType
substTys TCvSubst
subst ThetaType
arg_tys
; [DFunId]
ids1 <- FastString -> ThetaType -> TcRnIf TcGblEnv TcLclEnv [DFunId]
forall gbl lcl. FastString -> ThetaType -> TcRnIf gbl lcl [DFunId]
newSysLocalIds (String -> FastString
fsLit String
"dk") ThetaType
arg_tys'
; (TCvSubst
subst', [DFunId]
tvs1) <- TCvSubst -> [DFunId] -> TcM (TCvSubst, [DFunId])
tcInstSkolTyVarsX TCvSubst
subst [DFunId]
tvs
; [DFunId]
ev_vars1 <- ThetaType -> TcRnIf TcGblEnv TcLclEnv [DFunId]
newEvVars (HasCallStack => TCvSubst -> ThetaType -> ThetaType
TCvSubst -> ThetaType -> ThetaType
substTheta TCvSubst
subst' ThetaType
theta)
; (HsWrapper
wrap, [(Name, DFunId)]
tvs_prs2, [DFunId]
ev_vars2, Type
rho) <- TCvSubst
-> Type -> TcM (HsWrapper, [(Name, DFunId)], [DFunId], Type)
go TCvSubst
subst' Type
ty'
; let tv_prs1 :: [(Name, DFunId)]
tv_prs1 = (DFunId -> Name) -> [DFunId] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map DFunId -> Name
tyVarName [DFunId]
tvs [Name] -> [DFunId] -> [(Name, DFunId)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` [DFunId]
tvs1
; (HsWrapper, [(Name, DFunId)], [DFunId], Type)
-> TcM (HsWrapper, [(Name, DFunId)], [DFunId], Type)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ( [DFunId] -> HsWrapper
mkWpLams [DFunId]
ids1
HsWrapper -> HsWrapper -> HsWrapper
<.> [DFunId] -> HsWrapper
mkWpTyLams [DFunId]
tvs1
HsWrapper -> HsWrapper -> HsWrapper
<.> [DFunId] -> HsWrapper
mkWpLams [DFunId]
ev_vars1
HsWrapper -> HsWrapper -> HsWrapper
<.> HsWrapper
wrap
HsWrapper -> HsWrapper -> HsWrapper
<.> [DFunId] -> HsWrapper
mkWpEvVarApps [DFunId]
ids1
, [(Name, DFunId)]
tv_prs1 [(Name, DFunId)] -> [(Name, DFunId)] -> [(Name, DFunId)]
forall a. [a] -> [a] -> [a]
++ [(Name, DFunId)]
tvs_prs2
, [DFunId]
ev_vars1 [DFunId] -> [DFunId] -> [DFunId]
forall a. [a] -> [a] -> [a]
++ [DFunId]
ev_vars2
, ThetaType -> Type -> Type
mkVisFunTys ThetaType
arg_tys' Type
rho ) }
| Bool
otherwise
= (HsWrapper, [(Name, DFunId)], [DFunId], Type)
-> TcM (HsWrapper, [(Name, DFunId)], [DFunId], Type)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsWrapper
idHsWrapper, [], [], HasCallStack => TCvSubst -> Type -> Type
TCvSubst -> Type -> Type
substTy TCvSubst
subst Type
ty)
topInstantiate :: CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcRhoType)
topInstantiate :: CtOrigin -> Type -> TcM (HsWrapper, Type)
topInstantiate = Bool -> CtOrigin -> Type -> TcM (HsWrapper, Type)
top_instantiate Bool
True
topInstantiateInferred :: CtOrigin -> TcSigmaType
-> TcM (HsWrapper, TcSigmaType)
topInstantiateInferred :: CtOrigin -> Type -> TcM (HsWrapper, Type)
topInstantiateInferred = Bool -> CtOrigin -> Type -> TcM (HsWrapper, Type)
top_instantiate Bool
False
top_instantiate :: Bool
-> CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcRhoType)
top_instantiate :: Bool -> CtOrigin -> Type -> TcM (HsWrapper, Type)
top_instantiate Bool
inst_all CtOrigin
orig Type
ty
| Bool -> Bool
not ([VarBndr DFunId ArgFlag] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [VarBndr DFunId ArgFlag]
binders Bool -> Bool -> Bool
&& ThetaType -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null ThetaType
theta)
= do { let ([VarBndr DFunId ArgFlag]
inst_bndrs, [VarBndr DFunId ArgFlag]
leave_bndrs) = (VarBndr DFunId ArgFlag -> Bool)
-> [VarBndr DFunId ArgFlag]
-> ([VarBndr DFunId ArgFlag], [VarBndr DFunId ArgFlag])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span VarBndr DFunId ArgFlag -> Bool
forall {tv}. VarBndr tv ArgFlag -> Bool
should_inst [VarBndr DFunId ArgFlag]
binders
(ThetaType
inst_theta, ThetaType
leave_theta)
| [VarBndr DFunId ArgFlag] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [VarBndr DFunId ArgFlag]
leave_bndrs = (ThetaType
theta, [])
| Bool
otherwise = ([], ThetaType
theta)
in_scope :: InScopeSet
in_scope = VarSet -> InScopeSet
mkInScopeSet (Type -> VarSet
tyCoVarsOfType Type
ty)
empty_subst :: TCvSubst
empty_subst = InScopeSet -> TCvSubst
mkEmptyTCvSubst InScopeSet
in_scope
inst_tvs :: [DFunId]
inst_tvs = [VarBndr DFunId ArgFlag] -> [DFunId]
forall tv argf. [VarBndr tv argf] -> [tv]
binderVars [VarBndr DFunId ArgFlag]
inst_bndrs
; (TCvSubst
subst, [DFunId]
inst_tvs') <- (TCvSubst
-> DFunId -> IOEnv (Env TcGblEnv TcLclEnv) (TCvSubst, DFunId))
-> TCvSubst -> [DFunId] -> TcM (TCvSubst, [DFunId])
forall (m :: * -> *) acc x y.
Monad m =>
(acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y])
External instance of the constraint type forall m. Monad (IOEnv m)
mapAccumLM TCvSubst
-> DFunId -> IOEnv (Env TcGblEnv TcLclEnv) (TCvSubst, DFunId)
newMetaTyVarX TCvSubst
empty_subst [DFunId]
inst_tvs
; let inst_theta' :: ThetaType
inst_theta' = HasCallStack => TCvSubst -> ThetaType -> ThetaType
TCvSubst -> ThetaType -> ThetaType
substTheta TCvSubst
subst ThetaType
inst_theta
sigma' :: Type
sigma' = HasCallStack => TCvSubst -> Type -> Type
TCvSubst -> Type -> Type
substTy TCvSubst
subst ([VarBndr DFunId ArgFlag] -> Type -> Type
mkForAllTys [VarBndr DFunId ArgFlag]
leave_bndrs (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
ThetaType -> Type -> Type
mkPhiTy ThetaType
leave_theta Type
rho)
inst_tv_tys' :: ThetaType
inst_tv_tys' = [DFunId] -> ThetaType
mkTyVarTys [DFunId]
inst_tvs'
; HsWrapper
wrap1 <- CtOrigin
-> ThetaType
-> ThetaType
-> IOEnv (Env TcGblEnv TcLclEnv) HsWrapper
instCall CtOrigin
orig ThetaType
inst_tv_tys' ThetaType
inst_theta'
; String -> SDoc -> TcRn ()
traceTc String
"Instantiating"
([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"all tyvars?" SDoc -> SDoc -> SDoc
<+> Bool -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Bool
ppr Bool
inst_all
, String -> SDoc
text String
"origin" SDoc -> SDoc -> SDoc
<+> CtOrigin -> SDoc
pprCtOrigin CtOrigin
orig
, String -> SDoc
text String
"type" SDoc -> SDoc -> SDoc
<+> Type -> SDoc
debugPprType Type
ty
, String -> SDoc
text String
"theta" SDoc -> SDoc -> SDoc
<+> ThetaType -> 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 Type
ppr ThetaType
theta
, String -> SDoc
text String
"leave_bndrs" SDoc -> SDoc -> SDoc
<+> [VarBndr DFunId ArgFlag] -> 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 tv. Outputable tv => Outputable (VarBndr tv ArgFlag)
External instance of the constraint type Outputable DFunId
ppr [VarBndr DFunId ArgFlag]
leave_bndrs
, String -> SDoc
text String
"with" SDoc -> SDoc -> SDoc
<+> [SDoc] -> SDoc
vcat ((Type -> SDoc) -> ThetaType -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Type -> SDoc
debugPprType ThetaType
inst_tv_tys')
, String -> SDoc
text String
"theta:" SDoc -> SDoc -> SDoc
<+> ThetaType -> 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 Type
ppr ThetaType
inst_theta' ])
; (HsWrapper
wrap2, Type
rho2) <-
if [VarBndr DFunId ArgFlag] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [VarBndr DFunId ArgFlag]
leave_bndrs
then Bool -> CtOrigin -> Type -> TcM (HsWrapper, Type)
top_instantiate Bool
inst_all CtOrigin
orig Type
sigma'
else (HsWrapper, Type) -> TcM (HsWrapper, Type)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsWrapper
idHsWrapper, Type
sigma')
; (HsWrapper, Type) -> TcM (HsWrapper, Type)
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, Type
rho2) }
| Bool
otherwise = (HsWrapper, Type) -> TcM (HsWrapper, Type)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsWrapper
idHsWrapper, Type
ty)
where
([VarBndr DFunId ArgFlag]
binders, Type
phi) = Type -> ([VarBndr DFunId ArgFlag], Type)
tcSplitForAllVarBndrs Type
ty
(ThetaType
theta, Type
rho) = Type -> (ThetaType, Type)
tcSplitPhiTy Type
phi
should_inst :: VarBndr tv ArgFlag -> Bool
should_inst VarBndr tv ArgFlag
bndr
| Bool
inst_all = Bool
True
| Bool
otherwise = VarBndr tv ArgFlag -> ArgFlag
forall tv argf. VarBndr tv argf -> argf
binderArgFlag VarBndr tv ArgFlag
bndr ArgFlag -> ArgFlag -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq ArgFlag
== ArgFlag
Inferred
deeplyInstantiate :: CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcRhoType)
deeplyInstantiate :: CtOrigin -> Type -> TcM (HsWrapper, Type)
deeplyInstantiate CtOrigin
orig Type
ty =
CtOrigin -> TCvSubst -> Type -> TcM (HsWrapper, Type)
deeply_instantiate CtOrigin
orig
(InScopeSet -> TCvSubst
mkEmptyTCvSubst (VarSet -> InScopeSet
mkInScopeSet (Type -> VarSet
tyCoVarsOfType Type
ty)))
Type
ty
deeply_instantiate :: CtOrigin
-> TCvSubst
-> TcSigmaType -> TcM (HsWrapper, TcRhoType)
deeply_instantiate :: CtOrigin -> TCvSubst -> Type -> TcM (HsWrapper, Type)
deeply_instantiate CtOrigin
orig TCvSubst
subst Type
ty
| Just (ThetaType
arg_tys, [DFunId]
tvs, ThetaType
theta, Type
rho) <- Type -> Maybe (ThetaType, [DFunId], ThetaType, Type)
tcDeepSplitSigmaTy_maybe Type
ty
= do { (TCvSubst
subst', [DFunId]
tvs') <- TCvSubst -> [DFunId] -> TcM (TCvSubst, [DFunId])
newMetaTyVarsX TCvSubst
subst [DFunId]
tvs
; let arg_tys' :: ThetaType
arg_tys' = HasCallStack => TCvSubst -> ThetaType -> ThetaType
TCvSubst -> ThetaType -> ThetaType
substTys TCvSubst
subst' ThetaType
arg_tys
theta' :: ThetaType
theta' = HasCallStack => TCvSubst -> ThetaType -> ThetaType
TCvSubst -> ThetaType -> ThetaType
substTheta TCvSubst
subst' ThetaType
theta
; [DFunId]
ids1 <- FastString -> ThetaType -> TcRnIf TcGblEnv TcLclEnv [DFunId]
forall gbl lcl. FastString -> ThetaType -> TcRnIf gbl lcl [DFunId]
newSysLocalIds (String -> FastString
fsLit String
"di") ThetaType
arg_tys'
; HsWrapper
wrap1 <- CtOrigin
-> ThetaType
-> ThetaType
-> IOEnv (Env TcGblEnv TcLclEnv) HsWrapper
instCall CtOrigin
orig ([DFunId] -> ThetaType
mkTyVarTys [DFunId]
tvs') ThetaType
theta'
; String -> SDoc -> TcRn ()
traceTc String
"Instantiating (deeply)" ([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"origin" SDoc -> SDoc -> SDoc
<+> CtOrigin -> SDoc
pprCtOrigin CtOrigin
orig
, String -> SDoc
text String
"type" SDoc -> SDoc -> SDoc
<+> Type -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Type
ppr Type
ty
, String -> SDoc
text String
"with" SDoc -> SDoc -> SDoc
<+> [DFunId] -> 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 DFunId
ppr [DFunId]
tvs'
, String -> SDoc
text String
"args:" SDoc -> SDoc -> SDoc
<+> [DFunId] -> 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 DFunId
ppr [DFunId]
ids1
, String -> SDoc
text String
"theta:" SDoc -> SDoc -> SDoc
<+> ThetaType -> 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 Type
ppr ThetaType
theta'
, String -> SDoc
text String
"subst:" SDoc -> SDoc -> SDoc
<+> TCvSubst -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TCvSubst
ppr TCvSubst
subst'])
; (HsWrapper
wrap2, Type
rho2) <- CtOrigin -> TCvSubst -> Type -> TcM (HsWrapper, Type)
deeply_instantiate CtOrigin
orig TCvSubst
subst' Type
rho
; (HsWrapper, Type) -> TcM (HsWrapper, Type)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([DFunId] -> HsWrapper
mkWpLams [DFunId]
ids1
HsWrapper -> HsWrapper -> HsWrapper
<.> HsWrapper
wrap2
HsWrapper -> HsWrapper -> HsWrapper
<.> HsWrapper
wrap1
HsWrapper -> HsWrapper -> HsWrapper
<.> [DFunId] -> HsWrapper
mkWpEvVarApps [DFunId]
ids1,
ThetaType -> Type -> Type
mkVisFunTys ThetaType
arg_tys' Type
rho2) }
| Bool
otherwise
= do { let ty' :: Type
ty' = HasCallStack => TCvSubst -> Type -> Type
TCvSubst -> Type -> Type
substTy TCvSubst
subst Type
ty
; String -> SDoc -> TcRn ()
traceTc String
"deeply_instantiate final subst"
([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"origin:" SDoc -> SDoc -> SDoc
<+> CtOrigin -> SDoc
pprCtOrigin CtOrigin
orig
, String -> SDoc
text String
"type:" SDoc -> SDoc -> SDoc
<+> Type -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Type
ppr Type
ty
, String -> SDoc
text String
"new type:" SDoc -> SDoc -> SDoc
<+> Type -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Type
ppr Type
ty'
, String -> SDoc
text String
"subst:" SDoc -> SDoc -> SDoc
<+> TCvSubst -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TCvSubst
ppr TCvSubst
subst ])
; (HsWrapper, Type) -> TcM (HsWrapper, Type)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsWrapper
idHsWrapper, Type
ty') }
instTyVarsWith :: CtOrigin -> [TyVar] -> [TcType] -> TcM TCvSubst
instTyVarsWith :: CtOrigin -> [DFunId] -> ThetaType -> TcM TCvSubst
instTyVarsWith CtOrigin
orig [DFunId]
tvs ThetaType
tys
= TCvSubst -> [DFunId] -> ThetaType -> TcM TCvSubst
go TCvSubst
emptyTCvSubst [DFunId]
tvs ThetaType
tys
where
go :: TCvSubst -> [DFunId] -> ThetaType -> TcM TCvSubst
go TCvSubst
subst [] []
= TCvSubst -> TcM TCvSubst
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return TCvSubst
subst
go TCvSubst
subst (DFunId
tv:[DFunId]
tvs) (Type
ty:ThetaType
tys)
| Type
tv_kind HasDebugCallStack => Type -> Type -> Bool
Type -> Type -> Bool
External instance of the constraint type HasDebugCallStack
`tcEqType` Type
ty_kind
= TCvSubst -> [DFunId] -> ThetaType -> TcM TCvSubst
go (TCvSubst -> DFunId -> Type -> TCvSubst
extendTvSubstAndInScope TCvSubst
subst DFunId
tv Type
ty) [DFunId]
tvs ThetaType
tys
| Bool
otherwise
= do { Coercion
co <- CtOrigin -> TypeOrKind -> Role -> Type -> Type -> TcM Coercion
emitWantedEq CtOrigin
orig TypeOrKind
KindLevel Role
Nominal Type
ty_kind Type
tv_kind
; TCvSubst -> [DFunId] -> ThetaType -> TcM TCvSubst
go (TCvSubst -> DFunId -> Type -> TCvSubst
extendTvSubstAndInScope TCvSubst
subst DFunId
tv (Type
ty Type -> Coercion -> Type
`mkCastTy` Coercion
co)) [DFunId]
tvs ThetaType
tys }
where
tv_kind :: Type
tv_kind = HasCallStack => TCvSubst -> Type -> Type
TCvSubst -> Type -> Type
substTy TCvSubst
subst (DFunId -> Type
tyVarKind DFunId
tv)
ty_kind :: Type
ty_kind = HasDebugCallStack => Type -> Type
Type -> Type
External instance of the constraint type HasDebugCallStack
tcTypeKind Type
ty
go TCvSubst
_ [DFunId]
_ ThetaType
_ = String -> SDoc -> TcM TCvSubst
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"instTysWith" ([DFunId] -> 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 DFunId
ppr [DFunId]
tvs SDoc -> SDoc -> SDoc
$$ ThetaType -> 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 Type
ppr ThetaType
tys)
instCall :: CtOrigin -> [TcType] -> TcThetaType -> TcM HsWrapper
instCall :: CtOrigin
-> ThetaType
-> ThetaType
-> IOEnv (Env TcGblEnv TcLclEnv) HsWrapper
instCall CtOrigin
orig ThetaType
tys ThetaType
theta
= do { HsWrapper
dict_app <- CtOrigin -> ThetaType -> IOEnv (Env TcGblEnv TcLclEnv) HsWrapper
instCallConstraints CtOrigin
orig ThetaType
theta
; HsWrapper -> IOEnv (Env TcGblEnv TcLclEnv) HsWrapper
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsWrapper
dict_app HsWrapper -> HsWrapper -> HsWrapper
<.> ThetaType -> HsWrapper
mkWpTyApps ThetaType
tys) }
instCallConstraints :: CtOrigin -> TcThetaType -> TcM HsWrapper
instCallConstraints :: CtOrigin -> ThetaType -> IOEnv (Env TcGblEnv TcLclEnv) HsWrapper
instCallConstraints CtOrigin
orig ThetaType
preds
| ThetaType -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null ThetaType
preds
= HsWrapper -> IOEnv (Env TcGblEnv TcLclEnv) HsWrapper
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return HsWrapper
idHsWrapper
| Bool
otherwise
= do { [EvTerm]
evs <- (Type -> IOEnv (Env TcGblEnv TcLclEnv) EvTerm)
-> ThetaType -> IOEnv (Env TcGblEnv TcLclEnv) [EvTerm]
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 Type -> IOEnv (Env TcGblEnv TcLclEnv) EvTerm
go ThetaType
preds
; String -> SDoc -> TcRn ()
traceTc String
"instCallConstraints" ([EvTerm] -> 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 EvTerm
ppr [EvTerm]
evs)
; HsWrapper -> IOEnv (Env TcGblEnv TcLclEnv) HsWrapper
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([EvTerm] -> HsWrapper
mkWpEvApps [EvTerm]
evs) }
where
go :: TcPredType -> TcM EvTerm
go :: Type -> IOEnv (Env TcGblEnv TcLclEnv) EvTerm
go Type
pred
| Just (Role
Nominal, Type
ty1, Type
ty2) <- Type -> Maybe (Role, Type, Type)
getEqPredTys_maybe Type
pred
= do { Coercion
co <- Maybe (HsExpr GhcRn) -> Type -> Type -> TcM Coercion
unifyType Maybe (HsExpr GhcRn)
forall a. Maybe a
Nothing Type
ty1 Type
ty2
; EvTerm -> IOEnv (Env TcGblEnv TcLclEnv) EvTerm
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Coercion -> EvTerm
evCoercion Coercion
co) }
| Just (TyCon
tc, args :: ThetaType
args@[Type
_, Type
_, Type
ty1, Type
ty2]) <- HasDebugCallStack => Type -> Maybe (TyCon, ThetaType)
Type -> Maybe (TyCon, ThetaType)
External instance of the constraint type HasDebugCallStack
splitTyConApp_maybe Type
pred
, TyCon
tc TyCon -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
External instance of the constraint type Uniquable TyCon
`hasKey` Unique
heqTyConKey
= do { Coercion
co <- Maybe (HsExpr GhcRn) -> Type -> Type -> TcM Coercion
unifyType Maybe (HsExpr GhcRn)
forall a. Maybe a
Nothing Type
ty1 Type
ty2
; EvTerm -> IOEnv (Env TcGblEnv TcLclEnv) EvTerm
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (DFunId -> ThetaType -> [EvExpr] -> EvTerm
evDFunApp (DataCon -> DFunId
dataConWrapId DataCon
heqDataCon) ThetaType
args [Coercion -> EvExpr
forall b. Coercion -> Expr b
Coercion Coercion
co]) }
| Bool
otherwise
= CtOrigin -> Type -> IOEnv (Env TcGblEnv TcLclEnv) EvTerm
emitWanted CtOrigin
orig Type
pred
instDFunType :: DFunId -> [DFunInstType]
-> TcM ( [TcType]
, TcThetaType )
instDFunType :: DFunId -> [DFunInstType] -> TcM (ThetaType, ThetaType)
instDFunType DFunId
dfun_id [DFunInstType]
dfun_inst_tys
= do { (TCvSubst
subst, ThetaType
inst_tys) <- TCvSubst -> [DFunId] -> [DFunInstType] -> TcM (TCvSubst, ThetaType)
go TCvSubst
empty_subst [DFunId]
dfun_tvs [DFunInstType]
dfun_inst_tys
; (ThetaType, ThetaType) -> TcM (ThetaType, ThetaType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (ThetaType
inst_tys, HasCallStack => TCvSubst -> ThetaType -> ThetaType
TCvSubst -> ThetaType -> ThetaType
substTheta TCvSubst
subst ThetaType
dfun_theta) }
where
dfun_ty :: Type
dfun_ty = DFunId -> Type
idType DFunId
dfun_id
([DFunId]
dfun_tvs, ThetaType
dfun_theta, Type
_) = Type -> ([DFunId], ThetaType, Type)
tcSplitSigmaTy Type
dfun_ty
empty_subst :: TCvSubst
empty_subst = InScopeSet -> TCvSubst
mkEmptyTCvSubst (VarSet -> InScopeSet
mkInScopeSet (Type -> VarSet
tyCoVarsOfType Type
dfun_ty))
go :: TCvSubst -> [TyVar] -> [DFunInstType] -> TcM (TCvSubst, [TcType])
go :: TCvSubst -> [DFunId] -> [DFunInstType] -> TcM (TCvSubst, ThetaType)
go TCvSubst
subst [] [] = (TCvSubst, ThetaType) -> TcM (TCvSubst, ThetaType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TCvSubst
subst, [])
go TCvSubst
subst (DFunId
tv:[DFunId]
tvs) (Just Type
ty : [DFunInstType]
mb_tys)
= do { (TCvSubst
subst', ThetaType
tys) <- TCvSubst -> [DFunId] -> [DFunInstType] -> TcM (TCvSubst, ThetaType)
go (TCvSubst -> DFunId -> Type -> TCvSubst
extendTvSubstAndInScope TCvSubst
subst DFunId
tv Type
ty)
[DFunId]
tvs
[DFunInstType]
mb_tys
; (TCvSubst, ThetaType) -> TcM (TCvSubst, ThetaType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TCvSubst
subst', Type
ty Type -> ThetaType -> ThetaType
forall a. a -> [a] -> [a]
: ThetaType
tys) }
go TCvSubst
subst (DFunId
tv:[DFunId]
tvs) (DFunInstType
Nothing : [DFunInstType]
mb_tys)
= do { (TCvSubst
subst', DFunId
tv') <- TCvSubst
-> DFunId -> IOEnv (Env TcGblEnv TcLclEnv) (TCvSubst, DFunId)
newMetaTyVarX TCvSubst
subst DFunId
tv
; (TCvSubst
subst'', ThetaType
tys) <- TCvSubst -> [DFunId] -> [DFunInstType] -> TcM (TCvSubst, ThetaType)
go TCvSubst
subst' [DFunId]
tvs [DFunInstType]
mb_tys
; (TCvSubst, ThetaType) -> TcM (TCvSubst, ThetaType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TCvSubst
subst'', DFunId -> Type
mkTyVarTy DFunId
tv' Type -> ThetaType -> ThetaType
forall a. a -> [a] -> [a]
: ThetaType
tys) }
go TCvSubst
_ [DFunId]
_ [DFunInstType]
_ = String -> SDoc -> TcM (TCvSubst, ThetaType)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"instDFunTypes" (DFunId -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable DFunId
ppr DFunId
dfun_id SDoc -> SDoc -> SDoc
$$ [DFunInstType] -> 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. Outputable a => Outputable (Maybe a)
External instance of the constraint type Outputable Type
ppr [DFunInstType]
dfun_inst_tys)
instStupidTheta :: CtOrigin -> TcThetaType -> TcM ()
instStupidTheta :: CtOrigin -> ThetaType -> TcRn ()
instStupidTheta CtOrigin
orig ThetaType
theta
= do { HsWrapper
_co <- CtOrigin -> ThetaType -> IOEnv (Env TcGblEnv TcLclEnv) HsWrapper
instCallConstraints CtOrigin
orig ThetaType
theta
; () -> TcRn ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return () }
tcInstInvisibleTyBinders :: Int -> TcKind -> TcM ([TcType], TcKind)
tcInstInvisibleTyBinders :: Int -> Type -> TcM (ThetaType, Type)
tcInstInvisibleTyBinders Int
0 Type
kind
= (ThetaType, Type) -> TcM (ThetaType, Type)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([], Type
kind)
tcInstInvisibleTyBinders Int
n Type
ty
= Int -> TCvSubst -> Type -> TcM (ThetaType, Type)
forall {t}.
(Ord t, Num t) =>
t -> TCvSubst -> Type -> TcM (ThetaType, Type)
External instance of the constraint type Num Int
External instance of the constraint type Ord Int
go Int
n TCvSubst
empty_subst Type
ty
where
empty_subst :: TCvSubst
empty_subst = InScopeSet -> TCvSubst
mkEmptyTCvSubst (VarSet -> InScopeSet
mkInScopeSet (Type -> VarSet
tyCoVarsOfType Type
ty))
go :: t -> TCvSubst -> Type -> TcM (ThetaType, Type)
go t
n TCvSubst
subst Type
kind
| t
n t -> t -> Bool
forall a. Ord a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Ord t
> t
0
, Just (TyBinder
bndr, Type
body) <- Type -> Maybe (TyBinder, Type)
tcSplitPiTy_maybe Type
kind
, TyBinder -> Bool
isInvisibleBinder TyBinder
bndr
= do { (TCvSubst
subst', Type
arg) <- TCvSubst -> TyBinder -> TcM (TCvSubst, Type)
tcInstInvisibleTyBinder TCvSubst
subst TyBinder
bndr
; (ThetaType
args, Type
inner_ty) <- t -> TCvSubst -> Type -> TcM (ThetaType, Type)
go (t
nt -> t -> t
forall a. Num a => a -> a -> a
Evidence bound by a type signature of the constraint type Num t
-t
1) TCvSubst
subst' Type
body
; (ThetaType, Type) -> TcM (ThetaType, Type)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Type
argType -> ThetaType -> ThetaType
forall a. a -> [a] -> [a]
:ThetaType
args, Type
inner_ty) }
| Bool
otherwise
= (ThetaType, Type) -> TcM (ThetaType, Type)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([], HasCallStack => TCvSubst -> Type -> Type
TCvSubst -> Type -> Type
substTy TCvSubst
subst Type
kind)
tcInstInvisibleTyBinder :: TCvSubst -> TyBinder -> TcM (TCvSubst, TcType)
tcInstInvisibleTyBinder :: TCvSubst -> TyBinder -> TcM (TCvSubst, Type)
tcInstInvisibleTyBinder TCvSubst
subst (Named (Bndr DFunId
tv ArgFlag
_))
= do { (TCvSubst
subst', DFunId
tv') <- TCvSubst
-> DFunId -> IOEnv (Env TcGblEnv TcLclEnv) (TCvSubst, DFunId)
newMetaTyVarX TCvSubst
subst DFunId
tv
; (TCvSubst, Type) -> TcM (TCvSubst, Type)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TCvSubst
subst', DFunId -> Type
mkTyVarTy DFunId
tv') }
tcInstInvisibleTyBinder TCvSubst
subst (Anon AnonArgFlag
af Type
ty)
| Just (Coercion -> TcM Type
mk, Type
k1, Type
k2) <- Type -> Maybe (Coercion -> TcM Type, Type, Type)
get_eq_tys_maybe (HasCallStack => TCvSubst -> Type -> Type
TCvSubst -> Type -> Type
substTy TCvSubst
subst Type
ty)
= ASSERT( af == InvisArg )
do { Coercion
co <- Maybe (HsType GhcRn) -> Type -> Type -> TcM Coercion
unifyKind Maybe (HsType GhcRn)
forall a. Maybe a
Nothing Type
k1 Type
k2
; Type
arg' <- Coercion -> TcM Type
mk Coercion
co
; (TCvSubst, Type) -> TcM (TCvSubst, Type)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TCvSubst
subst, Type
arg') }
| Bool
otherwise
= String -> SDoc -> TcM (TCvSubst, Type)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"tcInvisibleTyBinder" (Type -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Type
ppr Type
ty)
get_eq_tys_maybe :: Type
-> Maybe ( Coercion -> TcM Type
, Type
, Type
)
get_eq_tys_maybe :: Type -> Maybe (Coercion -> TcM Type, Type, Type)
get_eq_tys_maybe Type
ty
| Just (TyCon
tc, [Type
_, Type
_, Type
k1, Type
k2]) <- HasDebugCallStack => Type -> Maybe (TyCon, ThetaType)
Type -> Maybe (TyCon, ThetaType)
External instance of the constraint type HasDebugCallStack
splitTyConApp_maybe Type
ty
, TyCon
tc TyCon -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
External instance of the constraint type Uniquable TyCon
`hasKey` Unique
heqTyConKey
= (Coercion -> TcM Type, Type, Type)
-> Maybe (Coercion -> TcM Type, Type, Type)
forall a. a -> Maybe a
Just (\Coercion
co -> Coercion -> Type -> Type -> TcM Type
mkHEqBoxTy Coercion
co Type
k1 Type
k2, Type
k1, Type
k2)
| Just (TyCon
tc, [Type
_, Type
k1, Type
k2]) <- HasDebugCallStack => Type -> Maybe (TyCon, ThetaType)
Type -> Maybe (TyCon, ThetaType)
External instance of the constraint type HasDebugCallStack
splitTyConApp_maybe Type
ty
, TyCon
tc TyCon -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
External instance of the constraint type Uniquable TyCon
`hasKey` Unique
eqTyConKey
= (Coercion -> TcM Type, Type, Type)
-> Maybe (Coercion -> TcM Type, Type, Type)
forall a. a -> Maybe a
Just (\Coercion
co -> Coercion -> Type -> Type -> TcM Type
mkEqBoxTy Coercion
co Type
k1 Type
k2, Type
k1, Type
k2)
| Bool
otherwise
= Maybe (Coercion -> TcM Type, Type, Type)
forall a. Maybe a
Nothing
mkHEqBoxTy :: TcCoercion -> Type -> Type -> TcM Type
mkHEqBoxTy :: Coercion -> Type -> Type -> TcM Type
mkHEqBoxTy Coercion
co Type
ty1 Type
ty2
= Type -> TcM Type
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Type -> TcM Type) -> Type -> TcM Type
forall a b. (a -> b) -> a -> b
$
TyCon -> ThetaType -> Type
mkTyConApp (DataCon -> TyCon
promoteDataCon DataCon
heqDataCon) [Type
k1, Type
k2, Type
ty1, Type
ty2, Coercion -> Type
mkCoercionTy Coercion
co]
where k1 :: Type
k1 = HasDebugCallStack => Type -> Type
Type -> Type
External instance of the constraint type HasDebugCallStack
tcTypeKind Type
ty1
k2 :: Type
k2 = HasDebugCallStack => Type -> Type
Type -> Type
External instance of the constraint type HasDebugCallStack
tcTypeKind Type
ty2
mkEqBoxTy :: TcCoercion -> Type -> Type -> TcM Type
mkEqBoxTy :: Coercion -> Type -> Type -> TcM Type
mkEqBoxTy Coercion
co Type
ty1 Type
ty2
= Type -> TcM Type
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Type -> TcM Type) -> Type -> TcM Type
forall a b. (a -> b) -> a -> b
$
TyCon -> ThetaType -> Type
mkTyConApp (DataCon -> TyCon
promoteDataCon DataCon
eqDataCon) [Type
k, Type
ty1, Type
ty2, Coercion -> Type
mkCoercionTy Coercion
co]
where k :: Type
k = HasDebugCallStack => Type -> Type
Type -> Type
External instance of the constraint type HasDebugCallStack
tcTypeKind Type
ty1
newOverloadedLit :: HsOverLit GhcRn
-> ExpRhoType
-> TcM (HsOverLit GhcTcId)
newOverloadedLit :: HsOverLit GhcRn -> ExpRhoType -> TcM (HsOverLit GhcTcId)
newOverloadedLit
lit :: HsOverLit GhcRn
lit@(OverLit { ol_val :: forall p. HsOverLit p -> OverLitVal
ol_val = OverLitVal
val, ol_ext :: forall p. HsOverLit p -> XOverLit p
ol_ext = XOverLit GhcRn
rebindable }) ExpRhoType
res_ty
| Bool -> Bool
not Bool
XOverLit GhcRn
rebindable
= do { Type
res_ty <- ExpRhoType -> TcM Type
expTypeToType ExpRhoType
res_ty
; 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
; let platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
; case Platform -> OverLitVal -> Type -> Maybe (HsExpr GhcTcId)
shortCutLit Platform
platform OverLitVal
val Type
res_ty of
Just HsExpr GhcTcId
expr -> HsOverLit GhcTcId -> TcM (HsOverLit GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsOverLit GhcRn
lit { ol_witness :: HsExpr GhcTcId
ol_witness = HsExpr GhcTcId
expr
, ol_ext :: XOverLit GhcTcId
ol_ext = Bool -> Type -> OverLitTc
OverLitTc Bool
False Type
res_ty })
Maybe (HsExpr GhcTcId)
Nothing -> CtOrigin
-> HsOverLit GhcRn -> ExpRhoType -> TcM (HsOverLit GhcTcId)
newNonTrivialOverloadedLit CtOrigin
orig HsOverLit GhcRn
lit
(Type -> ExpRhoType
mkCheckExpType Type
res_ty) }
| Bool
otherwise
= CtOrigin
-> HsOverLit GhcRn -> ExpRhoType -> TcM (HsOverLit GhcTcId)
newNonTrivialOverloadedLit CtOrigin
orig HsOverLit GhcRn
lit ExpRhoType
res_ty
where
orig :: CtOrigin
orig = HsOverLit GhcRn -> CtOrigin
LiteralOrigin HsOverLit GhcRn
lit
newNonTrivialOverloadedLit :: CtOrigin
-> HsOverLit GhcRn
-> ExpRhoType
-> TcM (HsOverLit GhcTcId)
newNonTrivialOverloadedLit :: CtOrigin
-> HsOverLit GhcRn -> ExpRhoType -> TcM (HsOverLit GhcTcId)
newNonTrivialOverloadedLit CtOrigin
orig
lit :: HsOverLit GhcRn
lit@(OverLit { ol_val :: forall p. HsOverLit p -> OverLitVal
ol_val = OverLitVal
val, ol_witness :: forall p. HsOverLit p -> HsExpr p
ol_witness = HsVar XVar GhcRn
_ (L SrcSpan
_ IdP GhcRn
meth_name)
, ol_ext :: forall p. HsOverLit p -> XOverLit p
ol_ext = XOverLit GhcRn
rebindable }) ExpRhoType
res_ty
= do { HsLit GhcTcId
hs_lit <- OverLitVal -> TcM (HsLit GhcTcId)
mkOverLit OverLitVal
val
; let lit_ty :: Type
lit_ty = HsLit GhcTcId -> Type
forall (p :: Pass). HsLit (GhcPass p) -> Type
hsLitType HsLit GhcTcId
hs_lit
; (()
_, SyntaxExprTc
fi') <- CtOrigin
-> SyntaxExprRn
-> [SyntaxOpType]
-> ExpRhoType
-> (ThetaType -> TcRn ())
-> TcM ((), SyntaxExprTc)
forall a.
CtOrigin
-> SyntaxExprRn
-> [SyntaxOpType]
-> ExpRhoType
-> (ThetaType -> TcM a)
-> TcM (a, SyntaxExprTc)
tcSyntaxOp CtOrigin
orig (Name -> SyntaxExprRn
mkRnSyntaxExpr Name
IdP GhcRn
meth_name)
[Type -> SyntaxOpType
synKnownType Type
lit_ty] ExpRhoType
res_ty ((ThetaType -> TcRn ()) -> TcM ((), SyntaxExprTc))
-> (ThetaType -> TcRn ()) -> TcM ((), SyntaxExprTc)
forall a b. (a -> b) -> a -> b
$
\ThetaType
_ -> () -> TcRn ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ()
; let L SrcSpan
_ HsExpr GhcTcId
witness = SyntaxExprTc
-> [GenLocated SrcSpan (HsExpr GhcTcId)]
-> GenLocated SrcSpan (HsExpr GhcTcId)
nlHsSyntaxApps SyntaxExprTc
fi' [HsLit GhcTcId -> GenLocated SrcSpan (HsExpr GhcTcId)
forall (p :: Pass). HsLit (GhcPass p) -> LHsExpr (GhcPass p)
nlHsLit HsLit GhcTcId
hs_lit]
; Type
res_ty <- ExpRhoType -> TcM Type
readExpType ExpRhoType
res_ty
; HsOverLit GhcTcId -> TcM (HsOverLit GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (HsOverLit GhcRn
lit { ol_witness :: HsExpr GhcTcId
ol_witness = HsExpr GhcTcId
witness
, ol_ext :: XOverLit GhcTcId
ol_ext = Bool -> Type -> OverLitTc
OverLitTc Bool
XOverLit GhcRn
rebindable Type
res_ty }) }
newNonTrivialOverloadedLit CtOrigin
_ HsOverLit GhcRn
lit ExpRhoType
_
= String -> SDoc -> TcM (HsOverLit GhcTcId)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"newNonTrivialOverloadedLit" (HsOverLit GhcRn -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall (p :: Pass).
OutputableBndrId p =>
Outputable (HsOverLit (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 HsOverLit GhcRn
lit)
mkOverLit ::OverLitVal -> TcM (HsLit GhcTc)
mkOverLit :: OverLitVal -> TcM (HsLit GhcTcId)
mkOverLit (HsIntegral IntegralLit
i)
= do { Type
integer_ty <- Name -> TcM Type
tcMetaTy Name
integerTyConName
; HsLit GhcTcId -> TcM (HsLit GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (XHsInteger GhcTcId -> Integer -> Type -> HsLit GhcTcId
forall x. XHsInteger x -> Integer -> Type -> HsLit x
HsInteger (IntegralLit -> SourceText
il_text IntegralLit
i)
(IntegralLit -> Integer
il_value IntegralLit
i) Type
integer_ty) }
mkOverLit (HsFractional FractionalLit
r)
= do { Type
rat_ty <- Name -> TcM Type
tcMetaTy Name
rationalTyConName
; HsLit GhcTcId -> TcM (HsLit GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (XHsRat GhcTcId -> FractionalLit -> Type -> HsLit GhcTcId
forall x. XHsRat x -> FractionalLit -> Type -> HsLit x
HsRat XHsRat GhcTcId
NoExtField
noExtField FractionalLit
r Type
rat_ty) }
mkOverLit (HsIsString SourceText
src FastString
s) = HsLit GhcTcId -> TcM (HsLit GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (XHsString GhcTcId -> FastString -> HsLit GhcTcId
forall x. XHsString x -> FastString -> HsLit x
HsString SourceText
XHsString GhcTcId
src FastString
s)
tcSyntaxName :: CtOrigin
-> TcType
-> (Name, HsExpr GhcRn)
-> TcM (Name, HsExpr GhcTcId)
tcSyntaxName :: CtOrigin
-> Type -> (Name, HsExpr GhcRn) -> TcM (Name, HsExpr GhcTcId)
tcSyntaxName CtOrigin
orig Type
ty (Name
std_nm, HsVar XVar GhcRn
_ (L SrcSpan
_ IdP GhcRn
user_nm))
| Name
std_nm Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Name
== Name
IdP GhcRn
user_nm
= do HsExpr GhcTcId
rhs <- CtOrigin -> Name -> ThetaType -> TcM (HsExpr GhcTcId)
newMethodFromName CtOrigin
orig Name
std_nm [Type
ty]
(Name, HsExpr GhcTcId) -> TcM (Name, HsExpr GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Name
std_nm, HsExpr GhcTcId
rhs)
tcSyntaxName CtOrigin
orig Type
ty (Name
std_nm, HsExpr GhcRn
user_nm_expr) = do
DFunId
std_id <- Name -> TcM DFunId
tcLookupId Name
std_nm
let
([DFunId
tv], ThetaType
_, Type
tau) = Type -> ([DFunId], ThetaType, Type)
tcSplitSigmaTy (DFunId -> Type
idType DFunId
std_id)
sigma1 :: Type
sigma1 = HasCallStack => [DFunId] -> ThetaType -> Type -> Type
[DFunId] -> ThetaType -> Type -> Type
substTyWith [DFunId
tv] [Type
ty] Type
tau
(TidyEnv -> TcM (TidyEnv, SDoc))
-> TcM (Name, HsExpr GhcTcId) -> TcM (Name, HsExpr GhcTcId)
forall a. (TidyEnv -> TcM (TidyEnv, SDoc)) -> TcM a -> TcM a
addErrCtxtM (HsExpr GhcRn -> CtOrigin -> Type -> TidyEnv -> TcM (TidyEnv, SDoc)
syntaxNameCtxt HsExpr GhcRn
user_nm_expr CtOrigin
orig Type
sigma1) (TcM (Name, HsExpr GhcTcId) -> TcM (Name, HsExpr GhcTcId))
-> TcM (Name, HsExpr GhcTcId) -> TcM (Name, HsExpr GhcTcId)
forall a b. (a -> b) -> a -> b
$ do
SrcSpan
span <- TcRn SrcSpan
getSrcSpanM
GenLocated SrcSpan (HsExpr GhcTcId)
expr <- LHsExpr GhcRn -> Type -> TcM (GenLocated SrcSpan (HsExpr GhcTcId))
tcCheckExpr (SrcSpan -> HsExpr GhcRn -> LHsExpr GhcRn
forall l e. l -> e -> GenLocated l e
L SrcSpan
span HsExpr GhcRn
user_nm_expr) Type
sigma1
(Name, HsExpr GhcTcId) -> TcM (Name, HsExpr GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Name
std_nm, GenLocated SrcSpan (HsExpr GhcTcId) -> HsExpr GhcTcId
forall l e. GenLocated l e -> e
unLoc GenLocated SrcSpan (HsExpr GhcTcId)
expr)
syntaxNameCtxt :: HsExpr GhcRn -> CtOrigin -> Type -> TidyEnv
-> TcRn (TidyEnv, SDoc)
syntaxNameCtxt :: HsExpr GhcRn -> CtOrigin -> Type -> TidyEnv -> TcM (TidyEnv, SDoc)
syntaxNameCtxt HsExpr GhcRn
name CtOrigin
orig Type
ty TidyEnv
tidy_env
= do { CtLoc
inst_loc <- CtOrigin -> Maybe TypeOrKind -> TcM CtLoc
getCtLocM CtOrigin
orig (TypeOrKind -> Maybe TypeOrKind
forall a. a -> Maybe a
Just TypeOrKind
TypeLevel)
; let msg :: SDoc
msg = [SDoc] -> SDoc
vcat [ String -> SDoc
text String
"When checking that" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (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
name)
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"(needed by a syntactic construct)"
, Int -> SDoc -> SDoc
nest Int
2 (String -> SDoc
text String
"has the required type:"
SDoc -> SDoc -> SDoc
<+> Type -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Type
ppr (TidyEnv -> Type -> Type
tidyType TidyEnv
tidy_env Type
ty))
, Int -> SDoc -> SDoc
nest Int
2 (CtLoc -> SDoc
pprCtLoc CtLoc
inst_loc) ]
; (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) }
getOverlapFlag :: Maybe OverlapMode -> TcM OverlapFlag
getOverlapFlag :: Maybe OverlapMode -> TcM OverlapFlag
getOverlapFlag Maybe OverlapMode
overlap_mode
= 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
; let overlap_ok :: Bool
overlap_ok = Extension -> DynFlags -> Bool
xopt Extension
LangExt.OverlappingInstances DynFlags
dflags
incoherent_ok :: Bool
incoherent_ok = Extension -> DynFlags -> Bool
xopt Extension
LangExt.IncoherentInstances DynFlags
dflags
use :: OverlapMode -> OverlapFlag
use OverlapMode
x = OverlapFlag :: OverlapMode -> Bool -> OverlapFlag
OverlapFlag { isSafeOverlap :: Bool
isSafeOverlap = DynFlags -> Bool
safeLanguageOn DynFlags
dflags
, overlapMode :: OverlapMode
overlapMode = OverlapMode
x }
default_oflag :: OverlapFlag
default_oflag | Bool
incoherent_ok = OverlapMode -> OverlapFlag
use (SourceText -> OverlapMode
Incoherent SourceText
NoSourceText)
| Bool
overlap_ok = OverlapMode -> OverlapFlag
use (SourceText -> OverlapMode
Overlaps SourceText
NoSourceText)
| Bool
otherwise = OverlapMode -> OverlapFlag
use (SourceText -> OverlapMode
NoOverlap SourceText
NoSourceText)
final_oflag :: OverlapFlag
final_oflag = OverlapFlag -> Maybe OverlapMode -> OverlapFlag
setOverlapModeMaybe OverlapFlag
default_oflag Maybe OverlapMode
overlap_mode
; OverlapFlag -> TcM OverlapFlag
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return OverlapFlag
final_oflag }
tcGetInsts :: TcM [ClsInst]
tcGetInsts :: TcM [ClsInst]
tcGetInsts = (TcGblEnv -> [ClsInst])
-> IOEnv (Env TcGblEnv TcLclEnv) TcGblEnv -> TcM [ClsInst]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall env. Functor (IOEnv env)
fmap TcGblEnv -> [ClsInst]
tcg_insts IOEnv (Env TcGblEnv TcLclEnv) TcGblEnv
forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
newClsInst :: Maybe OverlapMode -> Name -> [TyVar] -> ThetaType
-> Class -> [Type] -> TcM ClsInst
newClsInst :: Maybe OverlapMode
-> Name
-> [DFunId]
-> ThetaType
-> Class
-> ThetaType
-> TcM ClsInst
newClsInst Maybe OverlapMode
overlap_mode Name
dfun_name [DFunId]
tvs ThetaType
theta Class
clas ThetaType
tys
= do { (TCvSubst
subst, [DFunId]
tvs') <- [DFunId] -> TcM (TCvSubst, [DFunId])
freshenTyVarBndrs [DFunId]
tvs
; let tys' :: ThetaType
tys' = HasCallStack => TCvSubst -> ThetaType -> ThetaType
TCvSubst -> ThetaType -> ThetaType
substTys TCvSubst
subst ThetaType
tys
dfun :: DFunId
dfun = Name -> [DFunId] -> ThetaType -> Class -> ThetaType -> DFunId
mkDictFunId Name
dfun_name [DFunId]
tvs ThetaType
theta Class
clas ThetaType
tys
; OverlapFlag
oflag <- Maybe OverlapMode -> TcM OverlapFlag
getOverlapFlag Maybe OverlapMode
overlap_mode
; let inst :: ClsInst
inst = DFunId -> OverlapFlag -> [DFunId] -> Class -> ThetaType -> ClsInst
mkLocalInstance DFunId
dfun OverlapFlag
oflag [DFunId]
tvs' Class
clas ThetaType
tys'
; WarningFlag -> Bool -> SDoc -> TcRn ()
warnIfFlag WarningFlag
Opt_WarnOrphans
(IsOrphan -> Bool
isOrphan (ClsInst -> IsOrphan
is_orphan ClsInst
inst))
(ClsInst -> SDoc
instOrphWarn ClsInst
inst)
; ClsInst -> TcM ClsInst
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ClsInst
inst }
instOrphWarn :: ClsInst -> SDoc
instOrphWarn :: ClsInst -> SDoc
instOrphWarn ClsInst
inst
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"Orphan instance:") Int
2 (ClsInst -> SDoc
pprInstanceHdr ClsInst
inst)
SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
"To avoid this"
SDoc -> SDoc -> SDoc
$$ Int -> SDoc -> SDoc
nest Int
4 ([SDoc] -> SDoc
vcat [SDoc]
possibilities)
where
possibilities :: [SDoc]
possibilities =
String -> SDoc
text String
"move the instance declaration to the module of the class or of the type, or" SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
:
String -> SDoc
text String
"wrap the type with a newtype and declare the instance on the new type." SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
:
[]
tcExtendLocalInstEnv :: [ClsInst] -> TcM a -> TcM a
tcExtendLocalInstEnv :: [ClsInst] -> TcM a -> TcM a
tcExtendLocalInstEnv [ClsInst]
dfuns TcM a
thing_inside
= do { [ClsInst] -> TcRn ()
traceDFuns [ClsInst]
dfuns
; TcGblEnv
env <- IOEnv (Env TcGblEnv TcLclEnv) TcGblEnv
forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
; (InstEnv
inst_env', [ClsInst]
cls_insts') <- ((InstEnv, [ClsInst])
-> ClsInst -> IOEnv (Env TcGblEnv TcLclEnv) (InstEnv, [ClsInst]))
-> (InstEnv, [ClsInst])
-> [ClsInst]
-> IOEnv (Env TcGblEnv TcLclEnv) (InstEnv, [ClsInst])
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
External instance of the constraint type forall m. Monad (IOEnv m)
External instance of the constraint type Foldable []
foldlM (InstEnv, [ClsInst])
-> ClsInst -> IOEnv (Env TcGblEnv TcLclEnv) (InstEnv, [ClsInst])
addLocalInst
(TcGblEnv -> InstEnv
tcg_inst_env TcGblEnv
env, TcGblEnv -> [ClsInst]
tcg_insts TcGblEnv
env)
[ClsInst]
dfuns
; let env' :: TcGblEnv
env' = TcGblEnv
env { tcg_insts :: [ClsInst]
tcg_insts = [ClsInst]
cls_insts'
, tcg_inst_env :: InstEnv
tcg_inst_env = InstEnv
inst_env' }
; TcGblEnv -> TcM a -> TcM a
forall gbl lcl a. gbl -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
setGblEnv TcGblEnv
env' TcM a
thing_inside }
addLocalInst :: (InstEnv, [ClsInst]) -> ClsInst -> TcM (InstEnv, [ClsInst])
addLocalInst :: (InstEnv, [ClsInst])
-> ClsInst -> IOEnv (Env TcGblEnv TcLclEnv) (InstEnv, [ClsInst])
addLocalInst (InstEnv
home_ie, [ClsInst]
my_insts) ClsInst
ispec
= do {
; Bool
isGHCi <- TcRn Bool
getIsGHCi
; ExternalPackageState
eps <- TcRnIf TcGblEnv TcLclEnv ExternalPackageState
forall gbl lcl. TcRnIf gbl lcl ExternalPackageState
getEps
; TcGblEnv
tcg_env <- IOEnv (Env TcGblEnv TcLclEnv) TcGblEnv
forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
; let home_ie' :: InstEnv
home_ie'
| Bool
isGHCi = InstEnv -> ClsInst -> InstEnv
deleteFromInstEnv InstEnv
home_ie ClsInst
ispec
| Bool
otherwise = InstEnv
home_ie
global_ie :: InstEnv
global_ie = ExternalPackageState -> InstEnv
eps_inst_env ExternalPackageState
eps
inst_envs :: InstEnvs
inst_envs = InstEnvs :: InstEnv -> InstEnv -> VisibleOrphanModules -> InstEnvs
InstEnvs { ie_global :: InstEnv
ie_global = InstEnv
global_ie
, ie_local :: InstEnv
ie_local = InstEnv
home_ie'
, ie_visible :: VisibleOrphanModules
ie_visible = TcGblEnv -> VisibleOrphanModules
tcVisibleOrphanMods TcGblEnv
tcg_env }
; let inconsistent_ispecs :: [ClsInst]
inconsistent_ispecs = InstEnvs -> ClsInst -> [ClsInst]
checkFunDeps InstEnvs
inst_envs ClsInst
ispec
; Bool -> TcRn () -> TcRn ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type forall m. Applicative (IOEnv m)
unless ([ClsInst] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [ClsInst]
inconsistent_ispecs) (TcRn () -> TcRn ()) -> TcRn () -> TcRn ()
forall a b. (a -> b) -> a -> b
$
ClsInst -> [ClsInst] -> TcRn ()
funDepErr ClsInst
ispec [ClsInst]
inconsistent_ispecs
; let ([DFunId]
_tvs, Class
cls, ThetaType
tys) = ClsInst -> ([DFunId], Class, ThetaType)
instanceHead ClsInst
ispec
([InstMatch]
matches, [ClsInst]
_, [InstMatch]
_) = Bool
-> InstEnvs
-> Class
-> ThetaType
-> ([InstMatch], [ClsInst], [InstMatch])
lookupInstEnv Bool
False InstEnvs
inst_envs Class
cls ThetaType
tys
dups :: [ClsInst]
dups = (ClsInst -> Bool) -> [ClsInst] -> [ClsInst]
forall a. (a -> Bool) -> [a] -> [a]
filter (ClsInst -> ClsInst -> Bool
identicalClsInstHead ClsInst
ispec) ((InstMatch -> ClsInst) -> [InstMatch] -> [ClsInst]
forall a b. (a -> b) -> [a] -> [b]
map InstMatch -> ClsInst
forall a b. (a, b) -> a
fst [InstMatch]
matches)
; Bool -> TcRn () -> TcRn ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type forall m. Applicative (IOEnv m)
unless ([ClsInst] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [ClsInst]
dups) (TcRn () -> TcRn ()) -> TcRn () -> TcRn ()
forall a b. (a -> b) -> a -> b
$
ClsInst -> ClsInst -> TcRn ()
dupInstErr ClsInst
ispec ([ClsInst] -> ClsInst
forall a. [a] -> a
head [ClsInst]
dups)
; (InstEnv, [ClsInst])
-> IOEnv (Env TcGblEnv TcLclEnv) (InstEnv, [ClsInst])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (InstEnv -> ClsInst -> InstEnv
extendInstEnv InstEnv
home_ie' ClsInst
ispec, ClsInst
ispec ClsInst -> [ClsInst] -> [ClsInst]
forall a. a -> [a] -> [a]
: [ClsInst]
my_insts) }
traceDFuns :: [ClsInst] -> TcRn ()
traceDFuns :: [ClsInst] -> TcRn ()
traceDFuns [ClsInst]
ispecs
= String -> SDoc -> TcRn ()
traceTc String
"Adding instances:" ([SDoc] -> SDoc
vcat ((ClsInst -> SDoc) -> [ClsInst] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map ClsInst -> SDoc
pp [ClsInst]
ispecs))
where
pp :: ClsInst -> SDoc
pp ClsInst
ispec = SDoc -> Int -> SDoc -> SDoc
hang (DFunId -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable DFunId
ppr (ClsInst -> DFunId
instanceDFunId ClsInst
ispec) SDoc -> SDoc -> SDoc
<+> SDoc
colon)
Int
2 (ClsInst -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ClsInst
ppr ClsInst
ispec)
funDepErr :: ClsInst -> [ClsInst] -> TcRn ()
funDepErr :: ClsInst -> [ClsInst] -> TcRn ()
funDepErr ClsInst
ispec [ClsInst]
ispecs
= SDoc -> [ClsInst] -> TcRn ()
addClsInstsErr (String -> SDoc
text String
"Functional dependencies conflict between instance declarations:")
(ClsInst
ispec ClsInst -> [ClsInst] -> [ClsInst]
forall a. a -> [a] -> [a]
: [ClsInst]
ispecs)
dupInstErr :: ClsInst -> ClsInst -> TcRn ()
dupInstErr :: ClsInst -> ClsInst -> TcRn ()
dupInstErr ClsInst
ispec ClsInst
dup_ispec
= SDoc -> [ClsInst] -> TcRn ()
addClsInstsErr (String -> SDoc
text String
"Duplicate instance declarations:")
[ClsInst
ispec, ClsInst
dup_ispec]
addClsInstsErr :: SDoc -> [ClsInst] -> TcRn ()
addClsInstsErr :: SDoc -> [ClsInst] -> TcRn ()
addClsInstsErr SDoc
herald [ClsInst]
ispecs
= SrcSpan -> TcRn () -> TcRn ()
forall a. SrcSpan -> TcRn a -> TcRn a
setSrcSpan (ClsInst -> SrcSpan
forall a. NamedThing a => a -> SrcSpan
External instance of the constraint type NamedThing ClsInst
getSrcSpan ([ClsInst] -> ClsInst
forall a. [a] -> a
head [ClsInst]
sorted)) (TcRn () -> TcRn ()) -> TcRn () -> TcRn ()
forall a b. (a -> b) -> a -> b
$
SDoc -> TcRn ()
addErr (SDoc -> Int -> SDoc -> SDoc
hang SDoc
herald Int
2 ([ClsInst] -> SDoc
pprInstances [ClsInst]
sorted))
where
sorted :: [ClsInst]
sorted = (ClsInst -> ClsInst -> Ordering) -> [ClsInst] -> [ClsInst]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (SrcSpan -> SrcSpan -> Ordering
SrcLoc.leftmost_smallest (SrcSpan -> SrcSpan -> Ordering)
-> (ClsInst -> SrcSpan) -> ClsInst -> ClsInst -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` ClsInst -> SrcSpan
forall a. NamedThing a => a -> SrcSpan
External instance of the constraint type NamedThing ClsInst
getSrcSpan) [ClsInst]
ispecs