{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
module GHC.Tc.TyCl.Instance
( tcInstDecls1
, tcInstDeclsDeriv
, tcInstDecls2
)
where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Hs
import GHC.Tc.Gen.Bind
import GHC.Tc.TyCl
import GHC.Tc.TyCl.Utils ( addTyConsToGblEnv )
import GHC.Tc.TyCl.Class ( tcClassDecl2, tcATDefault,
HsSigFun, mkHsSigFun, badMethodErr,
findMethodBind, instantiateMethod )
import GHC.Tc.Gen.Sig
import GHC.Tc.Utils.Monad
import GHC.Tc.Validity
import GHC.Tc.Utils.Zonk
import GHC.Tc.Utils.TcMType
import GHC.Tc.Utils.TcType
import GHC.Tc.Types.Constraint
import GHC.Tc.Types.Origin
import GHC.Tc.TyCl.Build
import GHC.Tc.Utils.Instantiate
import GHC.Tc.Instance.Class( AssocInstInfo(..), isNotAssociated )
import GHC.Core.InstEnv
import GHC.Tc.Instance.Family
import GHC.Core.FamInstEnv
import GHC.Tc.Deriv
import GHC.Tc.Utils.Env
import GHC.Tc.Gen.HsType
import GHC.Tc.Utils.Unify
import GHC.Core ( Expr(..), mkApps, mkVarApps, mkLams )
import GHC.Core.Make ( nO_METHOD_BINDING_ERROR_ID )
import GHC.Core.Unfold ( mkInlineUnfoldingWithArity, mkDFunUnfolding )
import GHC.Core.Type
import GHC.Tc.Types.Evidence
import GHC.Core.TyCon
import GHC.Core.Coercion.Axiom
import GHC.Core.DataCon
import GHC.Core.ConLike
import GHC.Core.Class
import GHC.Types.Var as Var
import GHC.Types.Var.Env
import GHC.Types.Var.Set
import GHC.Data.Bag
import GHC.Types.Basic
import GHC.Driver.Session
import GHC.Utils.Error
import GHC.Data.FastString
import GHC.Types.Id
import GHC.Data.List.SetOps
import GHC.Types.Name
import GHC.Types.Name.Set
import GHC.Utils.Outputable
import GHC.Types.SrcLoc
import GHC.Utils.Misc
import GHC.Data.BooleanFormula ( isUnsatisfied, pprBooleanFormulaNice )
import qualified GHC.LanguageExtensions as LangExt
import Control.Monad
import Data.Tuple
import GHC.Data.Maybe
import Data.List( mapAccumL )
tcInstDecls1
:: [LInstDecl GhcRn]
-> TcM (TcGblEnv,
[InstInfo GhcRn],
[DerivInfo])
tcInstDecls1 :: [LInstDecl (GhcPass 'Renamed)]
-> TcM (TcGblEnv, [InstInfo (GhcPass 'Renamed)], [DerivInfo])
tcInstDecls1 [LInstDecl (GhcPass 'Renamed)]
inst_decls
= do {
; [([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])]
stuff <- (LInstDecl (GhcPass 'Renamed)
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo]))
-> [LInstDecl (GhcPass 'Renamed)]
-> TcRn [([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])]
forall a b. (a -> TcRn b) -> [a] -> TcRn [b]
mapAndRecoverM LInstDecl (GhcPass 'Renamed)
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
tcLocalInstDecl [LInstDecl (GhcPass 'Renamed)]
inst_decls
; let ([[InstInfo (GhcPass 'Renamed)]]
local_infos_s, [[FamInst]]
fam_insts_s, [[DerivInfo]]
datafam_deriv_infos) = [([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])]
-> ([[InstInfo (GhcPass 'Renamed)]], [[FamInst]], [[DerivInfo]])
forall a b c. [(a, b, c)] -> ([a], [b], [c])
unzip3 [([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])]
stuff
fam_insts :: [FamInst]
fam_insts = [[FamInst]] -> [FamInst]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
External instance of the constraint type Foldable []
concat [[FamInst]]
fam_insts_s
local_infos :: [InstInfo (GhcPass 'Renamed)]
local_infos = [[InstInfo (GhcPass 'Renamed)]] -> [InstInfo (GhcPass 'Renamed)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
External instance of the constraint type Foldable []
concat [[InstInfo (GhcPass 'Renamed)]]
local_infos_s
; TcGblEnv
gbl_env <- [InstInfo (GhcPass 'Renamed)] -> TcM TcGblEnv -> TcM TcGblEnv
forall a. [InstInfo (GhcPass 'Renamed)] -> TcM a -> TcM a
addClsInsts [InstInfo (GhcPass 'Renamed)]
local_infos (TcM TcGblEnv -> TcM TcGblEnv) -> TcM TcGblEnv -> TcM TcGblEnv
forall a b. (a -> b) -> a -> b
$
[FamInst] -> TcM TcGblEnv -> TcM TcGblEnv
forall a. [FamInst] -> TcM a -> TcM a
addFamInsts [FamInst]
fam_insts (TcM TcGblEnv -> TcM TcGblEnv) -> TcM TcGblEnv -> TcM TcGblEnv
forall a b. (a -> b) -> a -> b
$
TcM TcGblEnv
forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
; (TcGblEnv, [InstInfo (GhcPass 'Renamed)], [DerivInfo])
-> TcM (TcGblEnv, [InstInfo (GhcPass 'Renamed)], [DerivInfo])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ( TcGblEnv
gbl_env
, [InstInfo (GhcPass 'Renamed)]
local_infos
, [[DerivInfo]] -> [DerivInfo]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
External instance of the constraint type Foldable []
concat [[DerivInfo]]
datafam_deriv_infos ) }
tcInstDeclsDeriv
:: [DerivInfo]
-> [LDerivDecl GhcRn]
-> TcM (TcGblEnv, [InstInfo GhcRn], HsValBinds GhcRn)
tcInstDeclsDeriv :: [DerivInfo]
-> [LDerivDecl (GhcPass 'Renamed)]
-> TcM
(TcGblEnv, [InstInfo (GhcPass 'Renamed)],
HsValBinds (GhcPass 'Renamed))
tcInstDeclsDeriv [DerivInfo]
deriv_infos [LDerivDecl (GhcPass 'Renamed)]
derivds
= do ThStage
th_stage <- TcM ThStage
getStage
if ThStage -> Bool
isBrackStage ThStage
th_stage
then do { TcGblEnv
gbl_env <- TcM TcGblEnv
forall gbl lcl. TcRnIf gbl lcl gbl
getGblEnv
; (TcGblEnv, [InstInfo (GhcPass 'Renamed)],
HsValBinds (GhcPass 'Renamed))
-> TcM
(TcGblEnv, [InstInfo (GhcPass 'Renamed)],
HsValBinds (GhcPass 'Renamed))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcGblEnv
gbl_env, Bag (InstInfo (GhcPass 'Renamed)) -> [InstInfo (GhcPass 'Renamed)]
forall a. Bag a -> [a]
bagToList Bag (InstInfo (GhcPass 'Renamed))
forall a. Bag a
emptyBag, HsValBinds (GhcPass 'Renamed)
forall (a :: Pass) (b :: Pass).
HsValBindsLR (GhcPass a) (GhcPass b)
emptyValBindsOut) }
else do { (TcGblEnv
tcg_env, Bag (InstInfo (GhcPass 'Renamed))
info_bag, HsValBinds (GhcPass 'Renamed)
valbinds) <- [DerivInfo]
-> [LDerivDecl (GhcPass 'Renamed)]
-> TcM
(TcGblEnv, Bag (InstInfo (GhcPass 'Renamed)),
HsValBinds (GhcPass 'Renamed))
tcDeriving [DerivInfo]
deriv_infos [LDerivDecl (GhcPass 'Renamed)]
derivds
; (TcGblEnv, [InstInfo (GhcPass 'Renamed)],
HsValBinds (GhcPass 'Renamed))
-> TcM
(TcGblEnv, [InstInfo (GhcPass 'Renamed)],
HsValBinds (GhcPass 'Renamed))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TcGblEnv
tcg_env, Bag (InstInfo (GhcPass 'Renamed)) -> [InstInfo (GhcPass 'Renamed)]
forall a. Bag a -> [a]
bagToList Bag (InstInfo (GhcPass 'Renamed))
info_bag, HsValBinds (GhcPass 'Renamed)
valbinds) }
addClsInsts :: [InstInfo GhcRn] -> TcM a -> TcM a
addClsInsts :: [InstInfo (GhcPass 'Renamed)] -> TcM a -> TcM a
addClsInsts [InstInfo (GhcPass 'Renamed)]
infos TcM a
thing_inside
= [ClsInst] -> TcM a -> TcM a
forall a. [ClsInst] -> TcM a -> TcM a
tcExtendLocalInstEnv ((InstInfo (GhcPass 'Renamed) -> ClsInst)
-> [InstInfo (GhcPass 'Renamed)] -> [ClsInst]
forall a b. (a -> b) -> [a] -> [b]
map InstInfo (GhcPass 'Renamed) -> ClsInst
forall a. InstInfo a -> ClsInst
iSpec [InstInfo (GhcPass 'Renamed)]
infos) TcM a
thing_inside
addFamInsts :: [FamInst] -> TcM a -> TcM a
addFamInsts :: [FamInst] -> TcM a -> TcM a
addFamInsts [FamInst]
fam_insts TcM a
thing_inside
= [FamInst] -> TcM a -> TcM a
forall a. [FamInst] -> TcM a -> TcM a
tcExtendLocalFamInstEnv [FamInst]
fam_insts (TcM a -> TcM a) -> TcM a -> TcM a
forall a b. (a -> b) -> a -> b
$
[TyThing] -> TcM a -> TcM a
forall r. [TyThing] -> TcM r -> TcM r
tcExtendGlobalEnv [TyThing]
axioms (TcM a -> TcM a) -> TcM a -> TcM a
forall a b. (a -> b) -> a -> b
$
do { String -> SDoc -> TcRn ()
traceTc String
"addFamInsts" ([FamInst] -> SDoc
pprFamInsts [FamInst]
fam_insts)
; TcGblEnv
gbl_env <- [TyCon] -> TcM TcGblEnv
addTyConsToGblEnv [TyCon]
data_rep_tycons
; TcGblEnv -> TcM a -> TcM a
forall gbl lcl a. gbl -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
setGblEnv TcGblEnv
gbl_env TcM a
thing_inside }
where
axioms :: [TyThing]
axioms = (FamInst -> TyThing) -> [FamInst] -> [TyThing]
forall a b. (a -> b) -> [a] -> [b]
map (CoAxiom Branched -> TyThing
ACoAxiom (CoAxiom Branched -> TyThing)
-> (FamInst -> CoAxiom Branched) -> FamInst -> TyThing
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoAxiom Unbranched -> CoAxiom Branched
forall (br :: BranchFlag). CoAxiom br -> CoAxiom Branched
toBranchedAxiom (CoAxiom Unbranched -> CoAxiom Branched)
-> (FamInst -> CoAxiom Unbranched) -> FamInst -> CoAxiom Branched
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FamInst -> CoAxiom Unbranched
famInstAxiom) [FamInst]
fam_insts
data_rep_tycons :: [TyCon]
data_rep_tycons = [FamInst] -> [TyCon]
famInstsRepTyCons [FamInst]
fam_insts
tcLocalInstDecl :: LInstDecl GhcRn
-> TcM ([InstInfo GhcRn], [FamInst], [DerivInfo])
tcLocalInstDecl :: LInstDecl (GhcPass 'Renamed)
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
tcLocalInstDecl (L SrcSpan
loc (TyFamInstD { tfid_inst :: forall pass. InstDecl pass -> TyFamInstDecl pass
tfid_inst = TyFamInstDecl (GhcPass 'Renamed)
decl }))
= do { FamInst
fam_inst <- AssocInstInfo -> LTyFamInstDecl (GhcPass 'Renamed) -> TcM FamInst
tcTyFamInstDecl AssocInstInfo
NotAssociated (SrcSpan
-> TyFamInstDecl (GhcPass 'Renamed)
-> LTyFamInstDecl (GhcPass 'Renamed)
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc TyFamInstDecl (GhcPass 'Renamed)
decl)
; ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([], [FamInst
fam_inst], []) }
tcLocalInstDecl (L SrcSpan
loc (DataFamInstD { dfid_inst :: forall pass. InstDecl pass -> DataFamInstDecl pass
dfid_inst = DataFamInstDecl (GhcPass 'Renamed)
decl }))
= do { (FamInst
fam_inst, Maybe DerivInfo
m_deriv_info) <- AssocInstInfo
-> TyVarEnv Name
-> LDataFamInstDecl (GhcPass 'Renamed)
-> TcM (FamInst, Maybe DerivInfo)
tcDataFamInstDecl AssocInstInfo
NotAssociated TyVarEnv Name
forall a. VarEnv a
emptyVarEnv (SrcSpan
-> DataFamInstDecl (GhcPass 'Renamed)
-> LDataFamInstDecl (GhcPass 'Renamed)
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc DataFamInstDecl (GhcPass 'Renamed)
decl)
; ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([], [FamInst
fam_inst], Maybe DerivInfo -> [DerivInfo]
forall a. Maybe a -> [a]
maybeToList Maybe DerivInfo
m_deriv_info) }
tcLocalInstDecl (L SrcSpan
loc (ClsInstD { cid_inst :: forall pass. InstDecl pass -> ClsInstDecl pass
cid_inst = ClsInstDecl (GhcPass 'Renamed)
decl }))
= do { ([InstInfo (GhcPass 'Renamed)]
insts, [FamInst]
fam_insts, [DerivInfo]
deriv_infos) <- LClsInstDecl (GhcPass 'Renamed)
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
tcClsInstDecl (SrcSpan
-> ClsInstDecl (GhcPass 'Renamed)
-> LClsInstDecl (GhcPass 'Renamed)
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc ClsInstDecl (GhcPass 'Renamed)
decl)
; ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([InstInfo (GhcPass 'Renamed)]
insts, [FamInst]
fam_insts, [DerivInfo]
deriv_infos) }
tcClsInstDecl :: LClsInstDecl GhcRn
-> TcM ([InstInfo GhcRn], [FamInst], [DerivInfo])
tcClsInstDecl :: LClsInstDecl (GhcPass 'Renamed)
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
tcClsInstDecl (L SrcSpan
loc (ClsInstDecl { cid_poly_ty :: forall pass. ClsInstDecl pass -> LHsSigType pass
cid_poly_ty = LHsSigType (GhcPass 'Renamed)
hs_ty, cid_binds :: forall pass. ClsInstDecl pass -> LHsBinds pass
cid_binds = LHsBinds (GhcPass 'Renamed)
binds
, cid_sigs :: forall pass. ClsInstDecl pass -> [LSig pass]
cid_sigs = [LSig (GhcPass 'Renamed)]
uprags, cid_tyfam_insts :: forall pass. ClsInstDecl pass -> [LTyFamInstDecl pass]
cid_tyfam_insts = [LTyFamInstDecl (GhcPass 'Renamed)]
ats
, cid_overlap_mode :: forall pass. ClsInstDecl pass -> Maybe (Located OverlapMode)
cid_overlap_mode = Maybe (Located OverlapMode)
overlap_mode
, cid_datafam_insts :: forall pass. ClsInstDecl pass -> [LDataFamInstDecl pass]
cid_datafam_insts = [LDataFamInstDecl (GhcPass 'Renamed)]
adts }))
= SrcSpan
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
forall a. SrcSpan -> TcRn a -> TcRn a
setSrcSpan SrcSpan
loc (TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo]))
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
forall a b. (a -> b) -> a -> b
$
SDoc
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
forall a. SDoc -> TcM a -> TcM a
addErrCtxt (LHsSigType (GhcPass 'Renamed) -> SDoc
instDeclCtxt1 LHsSigType (GhcPass 'Renamed)
hs_ty) (TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo]))
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
forall a b. (a -> b) -> a -> b
$
do { PredType
dfun_ty <- UserTypeCtxt -> LHsSigType (GhcPass 'Renamed) -> TcM PredType
tcHsClsInstType (Bool -> UserTypeCtxt
InstDeclCtxt Bool
False) LHsSigType (GhcPass 'Renamed)
hs_ty
; let ([Id]
tyvars, [PredType]
theta, Class
clas, [PredType]
inst_tys) = PredType -> ([Id], [PredType], Class, [PredType])
tcSplitDFunTy PredType
dfun_ty
; (TCvSubst
subst, [Id]
skol_tvs) <- [Id] -> TcM (TCvSubst, [Id])
tcInstSkolTyVars [Id]
tyvars
; let tv_skol_prs :: [(Name, Id)]
tv_skol_prs = [ (Id -> Name
tyVarName Id
tv, Id
skol_tv)
| (Id
tv, Id
skol_tv) <- [Id]
tyvars [Id] -> [Id] -> [(Id, Id)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` [Id]
skol_tvs ]
tv_skol_env :: TyVarEnv Name
tv_skol_env = [(Id, Name)] -> TyVarEnv Name
forall a. [(Id, a)] -> VarEnv a
mkVarEnv ([(Id, Name)] -> TyVarEnv Name) -> [(Id, Name)] -> TyVarEnv Name
forall a b. (a -> b) -> a -> b
$ ((Name, Id) -> (Id, Name)) -> [(Name, Id)] -> [(Id, Name)]
forall a b. (a -> b) -> [a] -> [b]
map (Name, Id) -> (Id, Name)
forall a b. (a, b) -> (b, a)
swap [(Name, Id)]
tv_skol_prs
n_inferred :: ConTag
n_inferred = (VarBndr Id ArgFlag -> Bool) -> [VarBndr Id ArgFlag] -> ConTag
forall a. (a -> Bool) -> [a] -> ConTag
countWhile ((ArgFlag -> ArgFlag -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq ArgFlag
== ArgFlag
Inferred) (ArgFlag -> Bool)
-> (VarBndr Id ArgFlag -> ArgFlag) -> VarBndr Id ArgFlag -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VarBndr Id ArgFlag -> ArgFlag
forall tv argf. VarBndr tv argf -> argf
binderArgFlag) ([VarBndr Id ArgFlag] -> ConTag) -> [VarBndr Id ArgFlag] -> ConTag
forall a b. (a -> b) -> a -> b
$
([VarBndr Id ArgFlag], PredType) -> [VarBndr Id ArgFlag]
forall a b. (a, b) -> a
fst (([VarBndr Id ArgFlag], PredType) -> [VarBndr Id ArgFlag])
-> ([VarBndr Id ArgFlag], PredType) -> [VarBndr Id ArgFlag]
forall a b. (a -> b) -> a -> b
$ PredType -> ([VarBndr Id ArgFlag], PredType)
splitForAllVarBndrs PredType
dfun_ty
visible_skol_tvs :: [Id]
visible_skol_tvs = ConTag -> [Id] -> [Id]
forall a. ConTag -> [a] -> [a]
drop ConTag
n_inferred [Id]
skol_tvs
; String -> SDoc -> TcRn ()
traceTc String
"tcLocalInstDecl 1" (PredType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable PredType
ppr PredType
dfun_ty SDoc -> SDoc -> SDoc
$$ ConTag -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ConTag
ppr (PredType -> ConTag
invisibleTyBndrCount PredType
dfun_ty) SDoc -> SDoc -> SDoc
$$ [Id] -> 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 Id
ppr [Id]
skol_tvs)
; ([(FamInst, Maybe DerivInfo)]
datafam_stuff, [FamInst]
tyfam_insts)
<- [(Name, Id)]
-> TcM ([(FamInst, Maybe DerivInfo)], [FamInst])
-> TcM ([(FamInst, Maybe DerivInfo)], [FamInst])
forall r. [(Name, Id)] -> TcM r -> TcM r
tcExtendNameTyVarEnv [(Name, Id)]
tv_skol_prs (TcM ([(FamInst, Maybe DerivInfo)], [FamInst])
-> TcM ([(FamInst, Maybe DerivInfo)], [FamInst]))
-> TcM ([(FamInst, Maybe DerivInfo)], [FamInst])
-> TcM ([(FamInst, Maybe DerivInfo)], [FamInst])
forall a b. (a -> b) -> a -> b
$
do { let mini_env :: VarEnv PredType
mini_env = [(Id, PredType)] -> VarEnv PredType
forall a. [(Id, a)] -> VarEnv a
mkVarEnv (Class -> [Id]
classTyVars Class
clas [Id] -> [PredType] -> [(Id, PredType)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` HasCallStack => TCvSubst -> [PredType] -> [PredType]
TCvSubst -> [PredType] -> [PredType]
substTys TCvSubst
subst [PredType]
inst_tys)
mini_subst :: TCvSubst
mini_subst = InScopeSet -> VarEnv PredType -> TCvSubst
mkTvSubst (VarSet -> InScopeSet
mkInScopeSet ([Id] -> VarSet
mkVarSet [Id]
skol_tvs)) VarEnv PredType
mini_env
mb_info :: AssocInstInfo
mb_info = InClsInst :: Class -> [Id] -> VarEnv PredType -> AssocInstInfo
InClsInst { ai_class :: Class
ai_class = Class
clas
, ai_tyvars :: [Id]
ai_tyvars = [Id]
visible_skol_tvs
, ai_inst_env :: VarEnv PredType
ai_inst_env = VarEnv PredType
mini_env }
; [(FamInst, Maybe DerivInfo)]
df_stuff <- (LDataFamInstDecl (GhcPass 'Renamed)
-> TcM (FamInst, Maybe DerivInfo))
-> [LDataFamInstDecl (GhcPass 'Renamed)]
-> TcRn [(FamInst, Maybe DerivInfo)]
forall a b. (a -> TcRn b) -> [a] -> TcRn [b]
mapAndRecoverM (AssocInstInfo
-> TyVarEnv Name
-> LDataFamInstDecl (GhcPass 'Renamed)
-> TcM (FamInst, Maybe DerivInfo)
tcDataFamInstDecl AssocInstInfo
mb_info TyVarEnv Name
tv_skol_env) [LDataFamInstDecl (GhcPass 'Renamed)]
adts
; [FamInst]
tf_insts1 <- (LTyFamInstDecl (GhcPass 'Renamed) -> TcM FamInst)
-> [LTyFamInstDecl (GhcPass 'Renamed)] -> TcRn [FamInst]
forall a b. (a -> TcRn b) -> [a] -> TcRn [b]
mapAndRecoverM (AssocInstInfo -> LTyFamInstDecl (GhcPass 'Renamed) -> TcM FamInst
tcTyFamInstDecl AssocInstInfo
mb_info) [LTyFamInstDecl (GhcPass 'Renamed)]
ats
; [[FamInst]]
tf_insts2 <- (ClassATItem -> TcRn [FamInst])
-> [ClassATItem] -> IOEnv (Env TcGblEnv TcLclEnv) [[FamInst]]
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 (SrcSpan -> TCvSubst -> NameSet -> ClassATItem -> TcRn [FamInst]
tcATDefault SrcSpan
loc TCvSubst
mini_subst NameSet
defined_ats)
(Class -> [ClassATItem]
classATItems Class
clas)
; ([(FamInst, Maybe DerivInfo)], [FamInst])
-> TcM ([(FamInst, Maybe DerivInfo)], [FamInst])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([(FamInst, Maybe DerivInfo)]
df_stuff, [FamInst]
tf_insts1 [FamInst] -> [FamInst] -> [FamInst]
forall a. [a] -> [a] -> [a]
++ [[FamInst]] -> [FamInst]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
External instance of the constraint type Foldable []
concat [[FamInst]]
tf_insts2) }
; Name
dfun_name <- Class -> [PredType] -> SrcSpan -> TcM Name
newDFunName Class
clas [PredType]
inst_tys (LHsType (GhcPass 'Renamed) -> SrcSpan
forall l e. GenLocated l e -> l
getLoc (LHsSigType (GhcPass 'Renamed) -> LHsType (GhcPass 'Renamed)
forall (p :: Pass). LHsSigType (GhcPass p) -> LHsType (GhcPass p)
hsSigType LHsSigType (GhcPass 'Renamed)
hs_ty))
; ClsInst
ispec <- Maybe OverlapMode
-> Name -> [Id] -> [PredType] -> Class -> [PredType] -> TcM ClsInst
newClsInst ((Located OverlapMode -> OverlapMode)
-> Maybe (Located OverlapMode) -> Maybe OverlapMode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap Located OverlapMode -> OverlapMode
forall l e. GenLocated l e -> e
unLoc Maybe (Located OverlapMode)
overlap_mode) Name
dfun_name
[Id]
tyvars [PredType]
theta Class
clas [PredType]
inst_tys
; let inst_binds :: InstBindings (GhcPass 'Renamed)
inst_binds = InstBindings :: forall a.
[Name]
-> LHsBinds a -> [LSig a] -> [Extension] -> Bool -> InstBindings a
InstBindings
{ ib_binds :: LHsBinds (GhcPass 'Renamed)
ib_binds = LHsBinds (GhcPass 'Renamed)
binds
, ib_tyvars :: [Name]
ib_tyvars = (Id -> Name) -> [Id] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map Id -> Name
Var.varName [Id]
tyvars
, ib_pragmas :: [LSig (GhcPass 'Renamed)]
ib_pragmas = [LSig (GhcPass 'Renamed)]
uprags
, ib_extensions :: [Extension]
ib_extensions = []
, ib_derived :: Bool
ib_derived = Bool
False }
inst_info :: InstInfo (GhcPass 'Renamed)
inst_info = InstInfo :: forall a. ClsInst -> InstBindings a -> InstInfo a
InstInfo { iSpec :: ClsInst
iSpec = ClsInst
ispec, iBinds :: InstBindings (GhcPass 'Renamed)
iBinds = InstBindings (GhcPass 'Renamed)
inst_binds }
([FamInst]
datafam_insts, [Maybe DerivInfo]
m_deriv_infos) = [(FamInst, Maybe DerivInfo)] -> ([FamInst], [Maybe DerivInfo])
forall a b. [(a, b)] -> ([a], [b])
unzip [(FamInst, Maybe DerivInfo)]
datafam_stuff
deriv_infos :: [DerivInfo]
deriv_infos = [Maybe DerivInfo] -> [DerivInfo]
forall a. [Maybe a] -> [a]
catMaybes [Maybe DerivInfo]
m_deriv_infos
all_insts :: [FamInst]
all_insts = [FamInst]
tyfam_insts [FamInst] -> [FamInst] -> [FamInst]
forall a. [a] -> [a] -> [a]
++ [FamInst]
datafam_insts
; Bool
is_boot <- TcRn Bool
tcIsHsBootOrSig
; let no_binds :: Bool
no_binds = LHsBinds (GhcPass 'Renamed) -> Bool
forall idL idR. LHsBindsLR idL idR -> Bool
isEmptyLHsBinds LHsBinds (GhcPass 'Renamed)
binds Bool -> Bool -> Bool
&& [LSig (GhcPass 'Renamed)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
External instance of the constraint type Foldable []
null [LSig (GhcPass 'Renamed)]
uprags
; Bool -> SDoc -> TcRn ()
failIfTc (Bool
is_boot Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
no_binds) SDoc
badBootDeclErr
; ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
-> TcRn ([InstInfo (GhcPass 'Renamed)], [FamInst], [DerivInfo])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ( [InstInfo (GhcPass 'Renamed)
inst_info], [FamInst]
all_insts, [DerivInfo]
deriv_infos ) }
where
defined_ats :: NameSet
defined_ats = [Name] -> NameSet
mkNameSet ((LTyFamInstDecl (GhcPass 'Renamed) -> Name)
-> [LTyFamInstDecl (GhcPass 'Renamed)] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map (TyFamInstDecl (GhcPass 'Renamed) -> Name
forall (p :: Pass). TyFamInstDecl (GhcPass p) -> IdP (GhcPass p)
tyFamInstDeclName (TyFamInstDecl (GhcPass 'Renamed) -> Name)
-> (LTyFamInstDecl (GhcPass 'Renamed)
-> TyFamInstDecl (GhcPass 'Renamed))
-> LTyFamInstDecl (GhcPass 'Renamed)
-> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LTyFamInstDecl (GhcPass 'Renamed)
-> TyFamInstDecl (GhcPass 'Renamed)
forall l e. GenLocated l e -> e
unLoc) [LTyFamInstDecl (GhcPass 'Renamed)]
ats)
NameSet -> NameSet -> NameSet
`unionNameSet`
[Name] -> NameSet
mkNameSet ((LDataFamInstDecl (GhcPass 'Renamed) -> Name)
-> [LDataFamInstDecl (GhcPass 'Renamed)] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map (GenLocated SrcSpan Name -> Name
forall l e. GenLocated l e -> e
unLoc (GenLocated SrcSpan Name -> Name)
-> (LDataFamInstDecl (GhcPass 'Renamed) -> GenLocated SrcSpan Name)
-> LDataFamInstDecl (GhcPass 'Renamed)
-> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed))
-> GenLocated SrcSpan Name
forall pass rhs. FamEqn pass rhs -> Located (IdP pass)
feqn_tycon
(FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed))
-> GenLocated SrcSpan Name)
-> (LDataFamInstDecl (GhcPass 'Renamed)
-> FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed)))
-> LDataFamInstDecl (GhcPass 'Renamed)
-> GenLocated SrcSpan Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsImplicitBndrs
(GhcPass 'Renamed)
(FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed)))
-> FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed))
forall pass thing. HsImplicitBndrs pass thing -> thing
hsib_body
(HsImplicitBndrs
(GhcPass 'Renamed)
(FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed)))
-> FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed)))
-> (LDataFamInstDecl (GhcPass 'Renamed)
-> HsImplicitBndrs
(GhcPass 'Renamed)
(FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed))))
-> LDataFamInstDecl (GhcPass 'Renamed)
-> FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataFamInstDecl (GhcPass 'Renamed)
-> HsImplicitBndrs
(GhcPass 'Renamed)
(FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed)))
forall pass.
DataFamInstDecl pass -> FamInstEqn pass (HsDataDefn pass)
dfid_eqn
(DataFamInstDecl (GhcPass 'Renamed)
-> HsImplicitBndrs
(GhcPass 'Renamed)
(FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed))))
-> (LDataFamInstDecl (GhcPass 'Renamed)
-> DataFamInstDecl (GhcPass 'Renamed))
-> LDataFamInstDecl (GhcPass 'Renamed)
-> HsImplicitBndrs
(GhcPass 'Renamed)
(FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LDataFamInstDecl (GhcPass 'Renamed)
-> DataFamInstDecl (GhcPass 'Renamed)
forall l e. GenLocated l e -> e
unLoc) [LDataFamInstDecl (GhcPass 'Renamed)]
adts)
tcTyFamInstDecl :: AssocInstInfo
-> LTyFamInstDecl GhcRn -> TcM FamInst
tcTyFamInstDecl :: AssocInstInfo -> LTyFamInstDecl (GhcPass 'Renamed) -> TcM FamInst
tcTyFamInstDecl AssocInstInfo
mb_clsinfo (L SrcSpan
loc decl :: TyFamInstDecl (GhcPass 'Renamed)
decl@(TyFamInstDecl { tfid_eqn :: forall pass. TyFamInstDecl pass -> TyFamInstEqn pass
tfid_eqn = TyFamInstEqn (GhcPass 'Renamed)
eqn }))
= SrcSpan -> TcM FamInst -> TcM FamInst
forall a. SrcSpan -> TcRn a -> TcRn a
setSrcSpan SrcSpan
loc (TcM FamInst -> TcM FamInst) -> TcM FamInst -> TcM FamInst
forall a b. (a -> b) -> a -> b
$
TyFamInstDecl (GhcPass 'Renamed) -> TcM FamInst -> TcM FamInst
forall a. TyFamInstDecl (GhcPass 'Renamed) -> TcM a -> TcM a
tcAddTyFamInstCtxt TyFamInstDecl (GhcPass 'Renamed)
decl (TcM FamInst -> TcM FamInst) -> TcM FamInst -> TcM FamInst
forall a b. (a -> b) -> a -> b
$
do { let fam_lname :: Located (IdP (GhcPass 'Renamed))
fam_lname = FamEqn (GhcPass 'Renamed) (LHsType (GhcPass 'Renamed))
-> Located (IdP (GhcPass 'Renamed))
forall pass rhs. FamEqn pass rhs -> Located (IdP pass)
feqn_tycon (TyFamInstEqn (GhcPass 'Renamed)
-> FamEqn (GhcPass 'Renamed) (LHsType (GhcPass 'Renamed))
forall pass thing. HsImplicitBndrs pass thing -> thing
hsib_body TyFamInstEqn (GhcPass 'Renamed)
eqn)
; TyCon
fam_tc <- GenLocated SrcSpan Name -> TcM TyCon
tcLookupLocatedTyCon GenLocated SrcSpan Name
Located (IdP (GhcPass 'Renamed))
fam_lname
; AssocInstInfo -> TyCon -> TcRn ()
tcFamInstDeclChecks AssocInstInfo
mb_clsinfo TyCon
fam_tc
; Bool -> SDoc -> TcRn ()
checkTc (TyCon -> Bool
isTypeFamilyTyCon TyCon
fam_tc) (TyCon -> SDoc
wrongKindOfFamily TyCon
fam_tc)
; Bool -> SDoc -> TcRn ()
checkTc (TyCon -> Bool
isOpenTypeFamilyTyCon TyCon
fam_tc) (TyCon -> SDoc
notOpenFamily TyCon
fam_tc)
; KnotTied CoAxBranch
co_ax_branch <- TyCon
-> AssocInstInfo
-> LTyFamInstEqn (GhcPass 'Renamed)
-> TcM (KnotTied CoAxBranch)
tcTyFamInstEqn TyCon
fam_tc AssocInstInfo
mb_clsinfo
(SrcSpan
-> TyFamInstEqn (GhcPass 'Renamed)
-> LTyFamInstEqn (GhcPass 'Renamed)
forall l e. l -> e -> GenLocated l e
L (GenLocated SrcSpan Name -> SrcSpan
forall l e. GenLocated l e -> l
getLoc GenLocated SrcSpan Name
Located (IdP (GhcPass 'Renamed))
fam_lname) TyFamInstEqn (GhcPass 'Renamed)
eqn)
; AssocInstInfo -> TyCon -> KnotTied CoAxBranch -> TcRn ()
checkConsistentFamInst AssocInstInfo
mb_clsinfo TyCon
fam_tc KnotTied CoAxBranch
co_ax_branch
; TyCon -> KnotTied CoAxBranch -> TcRn ()
checkValidCoAxBranch TyCon
fam_tc KnotTied CoAxBranch
co_ax_branch
; Name
rep_tc_name <- GenLocated SrcSpan Name -> [[PredType]] -> TcM Name
newFamInstAxiomName GenLocated SrcSpan Name
Located (IdP (GhcPass 'Renamed))
fam_lname [KnotTied CoAxBranch -> [PredType]
coAxBranchLHS KnotTied CoAxBranch
co_ax_branch]
; let axiom :: CoAxiom Unbranched
axiom = Name -> TyCon -> KnotTied CoAxBranch -> CoAxiom Unbranched
mkUnbranchedCoAxiom Name
rep_tc_name TyCon
fam_tc KnotTied CoAxBranch
co_ax_branch
; FamFlavor -> CoAxiom Unbranched -> TcM FamInst
newFamInst FamFlavor
SynFamilyInst CoAxiom Unbranched
axiom }
tcFamInstDeclChecks :: AssocInstInfo -> TyCon -> TcM ()
tcFamInstDeclChecks :: AssocInstInfo -> TyCon -> TcRn ()
tcFamInstDeclChecks AssocInstInfo
mb_clsinfo TyCon
fam_tc
= do {
; String -> SDoc -> TcRn ()
traceTc String
"tcFamInstDecl" (TyCon -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TyCon
ppr TyCon
fam_tc)
; Bool
type_families <- Extension -> TcRn Bool
forall gbl lcl. Extension -> TcRnIf gbl lcl Bool
xoptM Extension
LangExt.TypeFamilies
; Bool
is_boot <- TcRn Bool
tcIsHsBootOrSig
; Bool -> SDoc -> TcRn ()
checkTc Bool
type_families (SDoc -> TcRn ()) -> SDoc -> TcRn ()
forall a b. (a -> b) -> a -> b
$ TyCon -> SDoc
badFamInstDecl TyCon
fam_tc
; Bool -> SDoc -> TcRn ()
checkTc (Bool -> Bool
not Bool
is_boot) (SDoc -> TcRn ()) -> SDoc -> TcRn ()
forall a b. (a -> b) -> a -> b
$ SDoc
badBootFamInstDeclErr
; Bool -> SDoc -> TcRn ()
checkTc (TyCon -> Bool
isFamilyTyCon TyCon
fam_tc) (TyCon -> SDoc
notFamily TyCon
fam_tc)
; Bool -> TcRn () -> TcRn ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type forall m. Applicative (IOEnv m)
when (AssocInstInfo -> Bool
isNotAssociated AssocInstInfo
mb_clsinfo Bool -> Bool -> Bool
&&
TyCon -> Bool
isTyConAssoc TyCon
fam_tc)
(SDoc -> TcRn ()
addErr (SDoc -> TcRn ()) -> SDoc -> TcRn ()
forall a b. (a -> b) -> a -> b
$ TyCon -> SDoc
assocInClassErr TyCon
fam_tc)
}
tcDataFamInstDecl ::
AssocInstInfo
-> TyVarEnv Name
-> LDataFamInstDecl GhcRn -> TcM (FamInst, Maybe DerivInfo)
tcDataFamInstDecl :: AssocInstInfo
-> TyVarEnv Name
-> LDataFamInstDecl (GhcPass 'Renamed)
-> TcM (FamInst, Maybe DerivInfo)
tcDataFamInstDecl AssocInstInfo
mb_clsinfo TyVarEnv Name
tv_skol_env
(L SrcSpan
loc decl :: DataFamInstDecl (GhcPass 'Renamed)
decl@(DataFamInstDecl { dfid_eqn :: forall pass.
DataFamInstDecl pass -> FamInstEqn pass (HsDataDefn pass)
dfid_eqn = HsIB { hsib_ext :: forall pass thing. HsImplicitBndrs pass thing -> XHsIB pass thing
hsib_ext = XHsIB
(GhcPass 'Renamed)
(FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed)))
imp_vars
, hsib_body :: forall pass thing. HsImplicitBndrs pass thing -> thing
hsib_body =
FamEqn { feqn_bndrs :: forall pass rhs. FamEqn pass rhs -> Maybe [LHsTyVarBndr () pass]
feqn_bndrs = Maybe [LHsTyVarBndr () (GhcPass 'Renamed)]
mb_bndrs
, feqn_pats :: forall pass rhs. FamEqn pass rhs -> HsTyPats pass
feqn_pats = HsTyPats (GhcPass 'Renamed)
hs_pats
, feqn_tycon :: forall pass rhs. FamEqn pass rhs -> Located (IdP pass)
feqn_tycon = lfam_name :: Located (IdP (GhcPass 'Renamed))
lfam_name@(L SrcSpan
_ IdP (GhcPass 'Renamed)
fam_name)
, feqn_fixity :: forall pass rhs. FamEqn pass rhs -> LexicalFixity
feqn_fixity = LexicalFixity
fixity
, feqn_rhs :: forall pass rhs. FamEqn pass rhs -> rhs
feqn_rhs = HsDataDefn { dd_ND :: forall pass. HsDataDefn pass -> NewOrData
dd_ND = NewOrData
new_or_data
, dd_cType :: forall pass. HsDataDefn pass -> Maybe (Located CType)
dd_cType = Maybe (Located CType)
cType
, dd_ctxt :: forall pass. HsDataDefn pass -> LHsContext pass
dd_ctxt = LHsContext (GhcPass 'Renamed)
hs_ctxt
, dd_cons :: forall pass. HsDataDefn pass -> [LConDecl pass]
dd_cons = [LConDecl (GhcPass 'Renamed)]
hs_cons
, dd_kindSig :: forall pass. HsDataDefn pass -> Maybe (LHsKind pass)
dd_kindSig = Maybe (LHsType (GhcPass 'Renamed))
m_ksig
, dd_derivs :: forall pass. HsDataDefn pass -> HsDeriving pass
dd_derivs = HsDeriving (GhcPass 'Renamed)
derivs } }}}))
= SrcSpan
-> TcM (FamInst, Maybe DerivInfo) -> TcM (FamInst, Maybe DerivInfo)
forall a. SrcSpan -> TcRn a -> TcRn a
setSrcSpan SrcSpan
loc (TcM (FamInst, Maybe DerivInfo) -> TcM (FamInst, Maybe DerivInfo))
-> TcM (FamInst, Maybe DerivInfo) -> TcM (FamInst, Maybe DerivInfo)
forall a b. (a -> b) -> a -> b
$
DataFamInstDecl (GhcPass 'Renamed)
-> TcM (FamInst, Maybe DerivInfo) -> TcM (FamInst, Maybe DerivInfo)
forall a. DataFamInstDecl (GhcPass 'Renamed) -> TcM a -> TcM a
tcAddDataFamInstCtxt DataFamInstDecl (GhcPass 'Renamed)
decl (TcM (FamInst, Maybe DerivInfo) -> TcM (FamInst, Maybe DerivInfo))
-> TcM (FamInst, Maybe DerivInfo) -> TcM (FamInst, Maybe DerivInfo)
forall a b. (a -> b) -> a -> b
$
do { TyCon
fam_tc <- GenLocated SrcSpan Name -> TcM TyCon
tcLookupLocatedTyCon GenLocated SrcSpan Name
Located (IdP (GhcPass 'Renamed))
lfam_name
; AssocInstInfo -> TyCon -> TcRn ()
tcFamInstDeclChecks AssocInstInfo
mb_clsinfo TyCon
fam_tc
; Bool -> SDoc -> TcRn ()
checkTc (TyCon -> Bool
isDataFamilyTyCon TyCon
fam_tc) (TyCon -> SDoc
wrongKindOfFamily TyCon
fam_tc)
; Bool
gadt_syntax <- Name
-> NewOrData
-> LHsContext (GhcPass 'Renamed)
-> [LConDecl (GhcPass 'Renamed)]
-> TcRn Bool
dataDeclChecks Name
IdP (GhcPass 'Renamed)
fam_name NewOrData
new_or_data LHsContext (GhcPass 'Renamed)
hs_ctxt [LConDecl (GhcPass 'Renamed)]
hs_cons
; ([Id]
qtvs, [PredType]
pats, PredType
res_kind, [PredType]
stupid_theta)
<- AssocInstInfo
-> TyCon
-> [Name]
-> Maybe [LHsTyVarBndr () (GhcPass 'Renamed)]
-> LexicalFixity
-> LHsContext (GhcPass 'Renamed)
-> HsTyPats (GhcPass 'Renamed)
-> Maybe (LHsType (GhcPass 'Renamed))
-> [LConDecl (GhcPass 'Renamed)]
-> NewOrData
-> TcM ([Id], [PredType], PredType, [PredType])
tcDataFamInstHeader AssocInstInfo
mb_clsinfo TyCon
fam_tc [Name]
XHsIB
(GhcPass 'Renamed)
(FamEqn (GhcPass 'Renamed) (HsDataDefn (GhcPass 'Renamed)))
imp_vars Maybe [LHsTyVarBndr () (GhcPass 'Renamed)]
mb_bndrs
LexicalFixity
fixity LHsContext (GhcPass 'Renamed)
hs_ctxt HsTyPats (GhcPass 'Renamed)
hs_pats Maybe (LHsType (GhcPass 'Renamed))
m_ksig [LConDecl (GhcPass 'Renamed)]
hs_cons
NewOrData
new_or_data
; let ([PredType]
eta_pats, [TyConBinder]
eta_tcbs) = TyCon -> [PredType] -> ([PredType], [TyConBinder])
eta_reduce TyCon
fam_tc [PredType]
pats
eta_tvs :: [Id]
eta_tvs = (TyConBinder -> Id) -> [TyConBinder] -> [Id]
forall a b. (a -> b) -> [a] -> [b]
map TyConBinder -> Id
forall tv argf. VarBndr tv argf -> tv
binderVar [TyConBinder]
eta_tcbs
post_eta_qtvs :: [Id]
post_eta_qtvs = (Id -> Bool) -> [Id] -> [Id]
forall a. (a -> Bool) -> [a] -> [a]
filterOut (Id -> [Id] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
External instance of the constraint type Eq Id
External instance of the constraint type Foldable []
`elem` [Id]
eta_tvs) [Id]
qtvs
full_tcbs :: [TyConBinder]
full_tcbs = [Id] -> VarSet -> [TyConBinder]
mkTyConBindersPreferAnon [Id]
post_eta_qtvs
(PredType -> VarSet
tyCoVarsOfType ([Id] -> PredType -> PredType
mkSpecForAllTys [Id]
eta_tvs PredType
res_kind))
[TyConBinder] -> [TyConBinder] -> [TyConBinder]
forall a. [a] -> [a] -> [a]
++ [TyConBinder]
eta_tcbs
; ([TyConBinder]
extra_tcbs, PredType
final_res_kind) <- [TyConBinder] -> PredType -> TcM ([TyConBinder], PredType)
etaExpandAlgTyCon [TyConBinder]
full_tcbs PredType
res_kind
; DataSort -> PredType -> TcRn ()
checkDataKindSig (NewOrData -> DataSort
DataInstanceSort NewOrData
new_or_data) PredType
final_res_kind
; let extra_pats :: [PredType]
extra_pats = (TyConBinder -> PredType) -> [TyConBinder] -> [PredType]
forall a b. (a -> b) -> [a] -> [b]
map (Id -> PredType
mkTyVarTy (Id -> PredType) -> (TyConBinder -> Id) -> TyConBinder -> PredType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyConBinder -> Id
forall tv argf. VarBndr tv argf -> tv
binderVar) [TyConBinder]
extra_tcbs
all_pats :: [PredType]
all_pats = [PredType]
pats [PredType] -> [PredType] -> [PredType]
forall a. [a] -> [a] -> [a]
`chkAppend` [PredType]
extra_pats
orig_res_ty :: PredType
orig_res_ty = TyCon -> [PredType] -> PredType
mkTyConApp TyCon
fam_tc [PredType]
all_pats
ty_binders :: [TyConBinder]
ty_binders = [TyConBinder]
full_tcbs [TyConBinder] -> [TyConBinder] -> [TyConBinder]
forall a. [a] -> [a] -> [a]
`chkAppend` [TyConBinder]
extra_tcbs
; String -> SDoc -> TcRn ()
traceTc String
"tcDataFamInstDecl" (SDoc -> TcRn ()) -> SDoc -> TcRn ()
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat [ String -> SDoc
text String
"Fam tycon:" SDoc -> SDoc -> SDoc
<+> TyCon -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TyCon
ppr TyCon
fam_tc
, String -> SDoc
text String
"Pats:" SDoc -> SDoc -> SDoc
<+> [PredType] -> 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 PredType
ppr [PredType]
pats
, String -> SDoc
text String
"visibliities:" SDoc -> SDoc -> SDoc
<+> [TyConBndrVis] -> 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 TyConBndrVis
ppr (TyCon -> [PredType] -> [TyConBndrVis]
tcbVisibilities TyCon
fam_tc [PredType]
pats)
, String -> SDoc
text String
"all_pats:" SDoc -> SDoc -> SDoc
<+> [PredType] -> 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 PredType
ppr [PredType]
all_pats
, String -> SDoc
text String
"ty_binders" SDoc -> SDoc -> SDoc
<+> [TyConBinder] -> 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.
OutputableBndr tv =>
Outputable (VarBndr tv TyConBndrVis)
External instance of the constraint type OutputableBndr Id
ppr [TyConBinder]
ty_binders
, String -> SDoc
text String
"fam_tc_binders:" SDoc -> SDoc -> SDoc
<+> [TyConBinder] -> 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.
OutputableBndr tv =>
Outputable (VarBndr tv TyConBndrVis)
External instance of the constraint type OutputableBndr Id
ppr (TyCon -> [TyConBinder]
tyConBinders TyCon
fam_tc)
, String -> SDoc
text String
"eta_pats" SDoc -> SDoc -> SDoc
<+> [PredType] -> 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 PredType
ppr [PredType]
eta_pats
, String -> SDoc
text String
"eta_tcbs" SDoc -> SDoc -> SDoc
<+> [TyConBinder] -> 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.
OutputableBndr tv =>
Outputable (VarBndr tv TyConBndrVis)
External instance of the constraint type OutputableBndr Id
ppr [TyConBinder]
eta_tcbs ]
; (TyCon
rep_tc, CoAxiom Unbranched
axiom) <- ((TyCon, CoAxiom Unbranched)
-> IOEnv (Env TcGblEnv TcLclEnv) (TyCon, CoAxiom Unbranched))
-> IOEnv (Env TcGblEnv TcLclEnv) (TyCon, CoAxiom Unbranched)
forall a env. (a -> IOEnv env a) -> IOEnv env a
fixM (((TyCon, CoAxiom Unbranched)
-> IOEnv (Env TcGblEnv TcLclEnv) (TyCon, CoAxiom Unbranched))
-> IOEnv (Env TcGblEnv TcLclEnv) (TyCon, CoAxiom Unbranched))
-> ((TyCon, CoAxiom Unbranched)
-> IOEnv (Env TcGblEnv TcLclEnv) (TyCon, CoAxiom Unbranched))
-> IOEnv (Env TcGblEnv TcLclEnv) (TyCon, CoAxiom Unbranched)
forall a b. (a -> b) -> a -> b
$ \ ~(TyCon
rec_rep_tc, CoAxiom Unbranched
_) ->
do { [DataCon]
data_cons <- [Id] -> TcM [DataCon] -> TcM [DataCon]
forall r. [Id] -> TcM r -> TcM r
tcExtendTyVarEnv [Id]
qtvs (TcM [DataCon] -> TcM [DataCon]) -> TcM [DataCon] -> TcM [DataCon]
forall a b. (a -> b) -> a -> b
$
TyCon
-> NewOrData
-> [TyConBinder]
-> PredType
-> PredType
-> [LConDecl (GhcPass 'Renamed)]
-> TcM [DataCon]
tcConDecls TyCon
rec_rep_tc NewOrData
new_or_data [TyConBinder]
ty_binders PredType
final_res_kind
PredType
orig_res_ty [LConDecl (GhcPass 'Renamed)]
hs_cons
; Name
rep_tc_name <- GenLocated SrcSpan Name -> [PredType] -> TcM Name
newFamInstTyConName GenLocated SrcSpan Name
Located (IdP (GhcPass 'Renamed))
lfam_name [PredType]
pats
; Name
axiom_name <- GenLocated SrcSpan Name -> [[PredType]] -> TcM Name
newFamInstAxiomName GenLocated SrcSpan Name
Located (IdP (GhcPass 'Renamed))
lfam_name [[PredType]
pats]
; AlgTyConRhs
tc_rhs <- case NewOrData
new_or_data of
NewOrData
DataType -> AlgTyConRhs -> IOEnv (Env TcGblEnv TcLclEnv) AlgTyConRhs
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([DataCon] -> AlgTyConRhs
mkDataTyConRhs [DataCon]
data_cons)
NewOrData
NewType -> ASSERT( not (null data_cons) )
Name
-> TyCon -> DataCon -> IOEnv (Env TcGblEnv TcLclEnv) AlgTyConRhs
forall m n. Name -> TyCon -> DataCon -> TcRnIf m n AlgTyConRhs
mkNewTyConRhs Name
rep_tc_name TyCon
rec_rep_tc ([DataCon] -> DataCon
forall a. [a] -> a
head [DataCon]
data_cons)
; let axiom :: CoAxiom Unbranched
axiom = Role
-> Name
-> [Id]
-> [Id]
-> [Id]
-> TyCon
-> [PredType]
-> PredType
-> CoAxiom Unbranched
mkSingleCoAxiom Role
Representational Name
axiom_name
[Id]
post_eta_qtvs [Id]
eta_tvs [] TyCon
fam_tc [PredType]
eta_pats
(TyCon -> [PredType] -> PredType
mkTyConApp TyCon
rep_tc ([Id] -> [PredType]
mkTyVarTys [Id]
post_eta_qtvs))
parent :: AlgTyConFlav
parent = CoAxiom Unbranched -> TyCon -> [PredType] -> AlgTyConFlav
DataFamInstTyCon CoAxiom Unbranched
axiom TyCon
fam_tc [PredType]
all_pats
rep_tc :: TyCon
rep_tc = Name
-> [TyConBinder]
-> PredType
-> [Role]
-> Maybe CType
-> [PredType]
-> AlgTyConRhs
-> AlgTyConFlav
-> Bool
-> TyCon
mkAlgTyCon Name
rep_tc_name
[TyConBinder]
ty_binders PredType
final_res_kind
((TyConBinder -> Role) -> [TyConBinder] -> [Role]
forall a b. (a -> b) -> [a] -> [b]
map (Role -> TyConBinder -> Role
forall a b. a -> b -> a
const Role
Nominal) [TyConBinder]
ty_binders)
((Located CType -> CType) -> Maybe (Located CType) -> Maybe CType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap Located CType -> CType
forall l e. GenLocated l e -> e
unLoc Maybe (Located CType)
cType) [PredType]
stupid_theta
AlgTyConRhs
tc_rhs AlgTyConFlav
parent
Bool
gadt_syntax
; (TyCon, CoAxiom Unbranched)
-> IOEnv (Env TcGblEnv TcLclEnv) (TyCon, CoAxiom Unbranched)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (TyCon
rep_tc, CoAxiom Unbranched
axiom) }
; let ax_branch :: KnotTied CoAxBranch
ax_branch = CoAxiom Unbranched -> KnotTied CoAxBranch
coAxiomSingleBranch CoAxiom Unbranched
axiom
; AssocInstInfo -> TyCon -> KnotTied CoAxBranch -> TcRn ()
checkConsistentFamInst AssocInstInfo
mb_clsinfo TyCon
fam_tc KnotTied CoAxBranch
ax_branch
; TyCon -> KnotTied CoAxBranch -> TcRn ()
checkValidCoAxBranch TyCon
fam_tc KnotTied CoAxBranch
ax_branch
; TyCon -> TcRn ()
checkValidTyCon TyCon
rep_tc
; let scoped_tvs :: [(Name, Id)]
scoped_tvs = (Id -> (Name, Id)) -> [Id] -> [(Name, Id)]
forall a b. (a -> b) -> [a] -> [b]
map Id -> (Name, Id)
mk_deriv_info_scoped_tv_pr (TyCon -> [Id]
tyConTyVars TyCon
rep_tc)
m_deriv_info :: Maybe DerivInfo
m_deriv_info = case HsDeriving (GhcPass 'Renamed)
derivs of
L SrcSpan
_ [] -> Maybe DerivInfo
forall a. Maybe a
Nothing
L SrcSpan
_ [LHsDerivingClause (GhcPass 'Renamed)]
preds ->
DerivInfo -> Maybe DerivInfo
forall a. a -> Maybe a
Just (DerivInfo -> Maybe DerivInfo) -> DerivInfo -> Maybe DerivInfo
forall a b. (a -> b) -> a -> b
$ DerivInfo :: TyCon
-> [(Name, Id)]
-> [LHsDerivingClause (GhcPass 'Renamed)]
-> SDoc
-> DerivInfo
DerivInfo { di_rep_tc :: TyCon
di_rep_tc = TyCon
rep_tc
, di_scoped_tvs :: [(Name, Id)]
di_scoped_tvs = [(Name, Id)]
scoped_tvs
, di_clauses :: [LHsDerivingClause (GhcPass 'Renamed)]
di_clauses = [LHsDerivingClause (GhcPass 'Renamed)]
preds
, di_ctxt :: SDoc
di_ctxt = DataFamInstDecl (GhcPass 'Renamed) -> SDoc
tcMkDataFamInstCtxt DataFamInstDecl (GhcPass 'Renamed)
decl }
; FamInst
fam_inst <- FamFlavor -> CoAxiom Unbranched -> TcM FamInst
newFamInst (TyCon -> FamFlavor
DataFamilyInst TyCon
rep_tc) CoAxiom Unbranched
axiom
; (FamInst, Maybe DerivInfo) -> TcM (FamInst, Maybe DerivInfo)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (FamInst
fam_inst, Maybe DerivInfo
m_deriv_info) }
where
eta_reduce :: TyCon -> [Type] -> ([Type], [TyConBinder])
eta_reduce :: TyCon -> [PredType] -> ([PredType], [TyConBinder])
eta_reduce TyCon
fam_tc [PredType]
pats
= [(PredType, VarSet, TyConBndrVis)]
-> [TyConBinder] -> ([PredType], [TyConBinder])
forall {c}.
[(PredType, VarSet, c)]
-> [VarBndr Id c] -> ([PredType], [VarBndr Id c])
go ([(PredType, VarSet, TyConBndrVis)]
-> [(PredType, VarSet, TyConBndrVis)]
forall a. [a] -> [a]
reverse ([PredType]
-> [VarSet] -> [TyConBndrVis] -> [(PredType, VarSet, TyConBndrVis)]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [PredType]
pats [VarSet]
fvs_s [TyConBndrVis]
vis_s)) []
where
vis_s :: [TyConBndrVis]
vis_s :: [TyConBndrVis]
vis_s = TyCon -> [PredType] -> [TyConBndrVis]
tcbVisibilities TyCon
fam_tc [PredType]
pats
fvs_s :: [TyCoVarSet]
(VarSet
_, [VarSet]
fvs_s) = (VarSet -> PredType -> (VarSet, VarSet))
-> VarSet -> [PredType] -> (VarSet, [VarSet])
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
External instance of the constraint type Traversable []
mapAccumL VarSet -> PredType -> (VarSet, VarSet)
add_fvs VarSet
emptyVarSet [PredType]
pats
add_fvs :: VarSet -> PredType -> (VarSet, VarSet)
add_fvs VarSet
fvs PredType
pat = (VarSet
fvs VarSet -> VarSet -> VarSet
`unionVarSet` PredType -> VarSet
tyCoVarsOfType PredType
pat, VarSet
fvs)
go :: [(PredType, VarSet, c)]
-> [VarBndr Id c] -> ([PredType], [VarBndr Id c])
go ((PredType
pat, VarSet
fvs_to_the_left, c
tcb_vis):[(PredType, VarSet, c)]
pats) [VarBndr Id c]
etad_tvs
| Just Id
tv <- PredType -> Maybe Id
getTyVar_maybe PredType
pat
, Bool -> Bool
not (Id
tv Id -> VarSet -> Bool
`elemVarSet` VarSet
fvs_to_the_left)
= [(PredType, VarSet, c)]
-> [VarBndr Id c] -> ([PredType], [VarBndr Id c])
go [(PredType, VarSet, c)]
pats (Id -> c -> VarBndr Id c
forall var argf. var -> argf -> VarBndr var argf
Bndr Id
tv c
tcb_vis VarBndr Id c -> [VarBndr Id c] -> [VarBndr Id c]
forall a. a -> [a] -> [a]
: [VarBndr Id c]
etad_tvs)
go [(PredType, VarSet, c)]
pats [VarBndr Id c]
etad_tvs = ([PredType] -> [PredType]
forall a. [a] -> [a]
reverse (((PredType, VarSet, c) -> PredType)
-> [(PredType, VarSet, c)] -> [PredType]
forall a b. (a -> b) -> [a] -> [b]
map (PredType, VarSet, c) -> PredType
forall a b c. (a, b, c) -> a
fstOf3 [(PredType, VarSet, c)]
pats), [VarBndr Id c]
etad_tvs)
mk_deriv_info_scoped_tv_pr :: TyVar -> (Name, TyVar)
mk_deriv_info_scoped_tv_pr :: Id -> (Name, Id)
mk_deriv_info_scoped_tv_pr Id
tv =
let n :: Name
n = TyVarEnv Name -> Name -> Id -> Name
forall a. VarEnv a -> a -> Id -> a
lookupWithDefaultVarEnv TyVarEnv Name
tv_skol_env (Id -> Name
tyVarName Id
tv) Id
tv
in (Name
n, Id
tv)
tcDataFamInstHeader
:: AssocInstInfo -> TyCon -> [Name] -> Maybe [LHsTyVarBndr () GhcRn]
-> LexicalFixity -> LHsContext GhcRn
-> HsTyPats GhcRn -> Maybe (LHsKind GhcRn) -> [LConDecl GhcRn]
-> NewOrData
-> TcM ([TyVar], [Type], Kind, ThetaType)
AssocInstInfo
mb_clsinfo TyCon
fam_tc [Name]
imp_vars Maybe [LHsTyVarBndr () (GhcPass 'Renamed)]
mb_bndrs LexicalFixity
fixity
LHsContext (GhcPass 'Renamed)
hs_ctxt HsTyPats (GhcPass 'Renamed)
hs_pats Maybe (LHsType (GhcPass 'Renamed))
m_ksig [LConDecl (GhcPass 'Renamed)]
hs_cons NewOrData
new_or_data
= do { ([Id]
imp_tvs, ([Id]
exp_tvs, ([PredType]
stupid_theta, PredType
lhs_ty, PredType
lhs_applied_kind)))
<- TcM ([Id], ([Id], ([PredType], PredType, PredType)))
-> TcM ([Id], ([Id], ([PredType], PredType, PredType)))
forall a. TcM a -> TcM a
pushTcLevelM_ (TcM ([Id], ([Id], ([PredType], PredType, PredType)))
-> TcM ([Id], ([Id], ([PredType], PredType, PredType))))
-> TcM ([Id], ([Id], ([PredType], PredType, PredType)))
-> TcM ([Id], ([Id], ([PredType], PredType, PredType)))
forall a b. (a -> b) -> a -> b
$
TcM ([Id], ([Id], ([PredType], PredType, PredType)))
-> TcM ([Id], ([Id], ([PredType], PredType, PredType)))
forall a. TcM a -> TcM a
solveEqualities (TcM ([Id], ([Id], ([PredType], PredType, PredType)))
-> TcM ([Id], ([Id], ([PredType], PredType, PredType))))
-> TcM ([Id], ([Id], ([PredType], PredType, PredType)))
-> TcM ([Id], ([Id], ([PredType], PredType, PredType)))
forall a b. (a -> b) -> a -> b
$
[Name]
-> TcM ([Id], ([PredType], PredType, PredType))
-> TcM ([Id], ([Id], ([PredType], PredType, PredType)))
forall a. [Name] -> TcM a -> TcM ([Id], a)
bindImplicitTKBndrs_Q_Skol [Name]
imp_vars (TcM ([Id], ([PredType], PredType, PredType))
-> TcM ([Id], ([Id], ([PredType], PredType, PredType))))
-> TcM ([Id], ([PredType], PredType, PredType))
-> TcM ([Id], ([Id], ([PredType], PredType, PredType)))
forall a b. (a -> b) -> a -> b
$
ContextKind
-> [LHsTyVarBndr () (GhcPass 'Renamed)]
-> TcM ([PredType], PredType, PredType)
-> TcM ([Id], ([PredType], PredType, PredType))
forall a.
ContextKind
-> [LHsTyVarBndr () (GhcPass 'Renamed)] -> TcM a -> TcM ([Id], a)
bindExplicitTKBndrs_Q_Skol ContextKind
AnyKind [LHsTyVarBndr () (GhcPass 'Renamed)]
exp_bndrs (TcM ([PredType], PredType, PredType)
-> TcM ([Id], ([PredType], PredType, PredType)))
-> TcM ([PredType], PredType, PredType)
-> TcM ([Id], ([PredType], PredType, PredType))
forall a b. (a -> b) -> a -> b
$
do { [PredType]
stupid_theta <- LHsContext (GhcPass 'Renamed) -> TcM [PredType]
tcHsContext LHsContext (GhcPass 'Renamed)
hs_ctxt
; (PredType
lhs_ty, PredType
lhs_kind) <- TyCon -> HsTyPats (GhcPass 'Renamed) -> TcM (PredType, PredType)
tcFamTyPats TyCon
fam_tc HsTyPats (GhcPass 'Renamed)
hs_pats
; AssocInstInfo -> PredType -> TcRn ()
addConsistencyConstraints AssocInstInfo
mb_clsinfo PredType
lhs_ty
; PredType
res_kind <- Maybe (LHsType (GhcPass 'Renamed)) -> TcM PredType
tc_kind_sig Maybe (LHsType (GhcPass 'Renamed))
m_ksig
; NewOrData -> PredType -> [LConDecl (GhcPass 'Renamed)] -> TcRn ()
kcConDecls NewOrData
new_or_data PredType
res_kind [LConDecl (GhcPass 'Renamed)]
hs_cons
; ([PredType]
lhs_extra_args, PredType
lhs_applied_kind)
<- ConTag -> PredType -> TcM ([PredType], PredType)
tcInstInvisibleTyBinders (PredType -> ConTag
invisibleTyBndrCount PredType
lhs_kind)
PredType
lhs_kind
; let lhs_applied_ty :: PredType
lhs_applied_ty = PredType
lhs_ty PredType -> [PredType] -> PredType
`mkTcAppTys` [PredType]
lhs_extra_args
hs_lhs :: LHsType (GhcPass 'Renamed)
hs_lhs = LexicalFixity
-> IdP (GhcPass 'Renamed)
-> HsTyPats (GhcPass 'Renamed)
-> LHsType (GhcPass 'Renamed)
forall (p :: Pass).
LexicalFixity
-> IdP (GhcPass p)
-> [LHsTypeArg (GhcPass p)]
-> LHsType (GhcPass p)
nlHsTyConApp LexicalFixity
fixity (TyCon -> Name
forall a. NamedThing a => a -> Name
External instance of the constraint type NamedThing TyCon
getName TyCon
fam_tc) HsTyPats (GhcPass 'Renamed)
hs_pats
; CoercionN
_ <- Maybe (HsType (GhcPass 'Renamed))
-> PredType -> PredType -> TcM CoercionN
unifyKind (HsType (GhcPass 'Renamed) -> Maybe (HsType (GhcPass 'Renamed))
forall a. a -> Maybe a
Just (LHsType (GhcPass 'Renamed) -> HsType (GhcPass 'Renamed)
forall l e. GenLocated l e -> e
unLoc LHsType (GhcPass 'Renamed)
hs_lhs)) PredType
lhs_applied_kind PredType
res_kind
; ([PredType], PredType, PredType)
-> TcM ([PredType], PredType, PredType)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ( [PredType]
stupid_theta
, PredType
lhs_applied_ty
, PredType
lhs_applied_kind ) }
; let scoped_tvs :: [Id]
scoped_tvs = [Id]
imp_tvs [Id] -> [Id] -> [Id]
forall a. [a] -> [a] -> [a]
++ [Id]
exp_tvs
; CandidatesQTvs
dvs <- [PredType] -> TcM CandidatesQTvs
candidateQTyVarsOfTypes (PredType
lhs_ty PredType -> [PredType] -> [PredType]
forall a. a -> [a] -> [a]
: [Id] -> [PredType]
mkTyVarTys [Id]
scoped_tvs)
; [Id]
qtvs <- CandidatesQTvs -> TcM [Id]
quantifyTyVars CandidatesQTvs
dvs
; (ZonkEnv
ze, [Id]
qtvs) <- [Id] -> TcM (ZonkEnv, [Id])
zonkTyBndrs [Id]
qtvs
; PredType
lhs_ty <- ZonkEnv -> PredType -> TcM PredType
zonkTcTypeToTypeX ZonkEnv
ze PredType
lhs_ty
; [PredType]
stupid_theta <- ZonkEnv -> [PredType] -> TcM [PredType]
zonkTcTypesToTypesX ZonkEnv
ze [PredType]
stupid_theta
; PredType
lhs_applied_kind <- ZonkEnv -> PredType -> TcM PredType
zonkTcTypeToTypeX ZonkEnv
ze PredType
lhs_applied_kind
; [PredType]
pats <- case HasDebugCallStack => PredType -> Maybe (TyCon, [PredType])
PredType -> Maybe (TyCon, [PredType])
External instance of the constraint type HasDebugCallStack
splitTyConApp_maybe PredType
lhs_ty of
Just (TyCon
_, [PredType]
pats) -> [PredType] -> TcM [PredType]
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall m. Applicative (IOEnv m)
pure [PredType]
pats
Maybe (TyCon, [PredType])
Nothing -> String -> SDoc -> TcM [PredType]
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"tcDataFamInstHeader" (PredType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable PredType
ppr PredType
lhs_ty)
; ([Id], [PredType], PredType, [PredType])
-> TcM ([Id], [PredType], PredType, [PredType])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([Id]
qtvs, [PredType]
pats, PredType
lhs_applied_kind, [PredType]
stupid_theta) }
where
fam_name :: Name
fam_name = TyCon -> Name
tyConName TyCon
fam_tc
data_ctxt :: UserTypeCtxt
data_ctxt = Name -> UserTypeCtxt
DataKindCtxt Name
fam_name
exp_bndrs :: [LHsTyVarBndr () (GhcPass 'Renamed)]
exp_bndrs = Maybe [LHsTyVarBndr () (GhcPass 'Renamed)]
mb_bndrs Maybe [LHsTyVarBndr () (GhcPass 'Renamed)]
-> [LHsTyVarBndr () (GhcPass 'Renamed)]
-> [LHsTyVarBndr () (GhcPass 'Renamed)]
forall a. Maybe a -> a -> a
`orElse` []
tc_kind_sig :: Maybe (LHsType (GhcPass 'Renamed)) -> TcM PredType
tc_kind_sig Maybe (LHsType (GhcPass 'Renamed))
Nothing
= do { Bool
unlifted_newtypes <- Extension -> TcRn Bool
forall gbl lcl. Extension -> TcRnIf gbl lcl Bool
xoptM Extension
LangExt.UnliftedNewtypes
; if Bool
unlifted_newtypes Bool -> Bool -> Bool
&& NewOrData
new_or_data NewOrData -> NewOrData -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq NewOrData
== NewOrData
NewType
then TcM PredType
newOpenTypeKind
else PredType -> TcM PredType
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall m. Applicative (IOEnv m)
pure PredType
liftedTypeKind
}
tc_kind_sig (Just LHsType (GhcPass 'Renamed)
hs_kind)
= do { PredType
sig_kind <- UserTypeCtxt -> LHsType (GhcPass 'Renamed) -> TcM PredType
tcLHsKindSig UserTypeCtxt
data_ctxt LHsType (GhcPass 'Renamed)
hs_kind
; let ([Id]
tvs, PredType
inner_kind) = PredType -> ([Id], PredType)
tcSplitForAllTys PredType
sig_kind
; TcLevel
lvl <- TcM TcLevel
getTcLevel
; (TCvSubst
subst, [Id]
_tvs') <- TcLevel -> Bool -> TCvSubst -> [Id] -> TcM (TCvSubst, [Id])
tcInstSkolTyVarsAt TcLevel
lvl Bool
False TCvSubst
emptyTCvSubst [Id]
tvs
; let final_kind :: PredType
final_kind = HasCallStack => TCvSubst -> PredType -> PredType
TCvSubst -> PredType -> PredType
substTy TCvSubst
subst PredType
inner_kind
; DataSort -> PredType -> TcRn ()
checkDataKindSig (NewOrData -> DataSort
DataInstanceSort NewOrData
new_or_data) (PredType -> TcRn ()) -> PredType -> TcRn ()
forall a b. (a -> b) -> a -> b
$
([TyBinder], PredType) -> PredType
forall a b. (a, b) -> b
snd (([TyBinder], PredType) -> PredType)
-> ([TyBinder], PredType) -> PredType
forall a b. (a -> b) -> a -> b
$ PredType -> ([TyBinder], PredType)
tcSplitPiTys PredType
final_kind
; PredType -> TcM PredType
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return PredType
final_kind }
tcInstDecls2 :: [LTyClDecl GhcRn] -> [InstInfo GhcRn]
-> TcM (LHsBinds GhcTc)
tcInstDecls2 :: [LTyClDecl (GhcPass 'Renamed)]
-> [InstInfo (GhcPass 'Renamed)] -> TcM (LHsBinds GhcTcId)
tcInstDecls2 [LTyClDecl (GhcPass 'Renamed)]
tycl_decls [InstInfo (GhcPass 'Renamed)]
inst_decls
= do {
let class_decls :: [LTyClDecl (GhcPass 'Renamed)]
class_decls = (LTyClDecl (GhcPass 'Renamed) -> Bool)
-> [LTyClDecl (GhcPass 'Renamed)] -> [LTyClDecl (GhcPass 'Renamed)]
forall a. (a -> Bool) -> [a] -> [a]
filter (TyClDecl (GhcPass 'Renamed) -> Bool
forall pass. TyClDecl pass -> Bool
isClassDecl (TyClDecl (GhcPass 'Renamed) -> Bool)
-> (LTyClDecl (GhcPass 'Renamed) -> TyClDecl (GhcPass 'Renamed))
-> LTyClDecl (GhcPass 'Renamed)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LTyClDecl (GhcPass 'Renamed) -> TyClDecl (GhcPass 'Renamed)
forall l e. GenLocated l e -> e
unLoc) [LTyClDecl (GhcPass 'Renamed)]
tycl_decls
; [LHsBinds GhcTcId]
dm_binds_s <- (LTyClDecl (GhcPass 'Renamed) -> TcM (LHsBinds GhcTcId))
-> [LTyClDecl (GhcPass 'Renamed)]
-> IOEnv (Env TcGblEnv TcLclEnv) [LHsBinds GhcTcId]
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 LTyClDecl (GhcPass 'Renamed) -> TcM (LHsBinds GhcTcId)
tcClassDecl2 [LTyClDecl (GhcPass 'Renamed)]
class_decls
; let dm_binds :: LHsBinds GhcTcId
dm_binds = [LHsBinds GhcTcId] -> LHsBinds GhcTcId
forall a. [Bag a] -> Bag a
unionManyBags [LHsBinds GhcTcId]
dm_binds_s
; let dm_ids :: [IdP GhcTcId]
dm_ids = LHsBinds GhcTcId -> [IdP GhcTcId]
forall p idR. CollectPass p => LHsBindsLR p idR -> [IdP p]
External instance of the constraint type CollectPass GhcTcId
collectHsBindsBinders LHsBinds GhcTcId
dm_binds
; [LHsBinds GhcTcId]
inst_binds_s <- [Id]
-> IOEnv (Env TcGblEnv TcLclEnv) [LHsBinds GhcTcId]
-> IOEnv (Env TcGblEnv TcLclEnv) [LHsBinds GhcTcId]
forall r. [Id] -> TcM r -> TcM r
tcExtendGlobalValEnv [Id]
[IdP GhcTcId]
dm_ids (IOEnv (Env TcGblEnv TcLclEnv) [LHsBinds GhcTcId]
-> IOEnv (Env TcGblEnv TcLclEnv) [LHsBinds GhcTcId])
-> IOEnv (Env TcGblEnv TcLclEnv) [LHsBinds GhcTcId]
-> IOEnv (Env TcGblEnv TcLclEnv) [LHsBinds GhcTcId]
forall a b. (a -> b) -> a -> b
$
(InstInfo (GhcPass 'Renamed) -> TcM (LHsBinds GhcTcId))
-> [InstInfo (GhcPass 'Renamed)]
-> IOEnv (Env TcGblEnv TcLclEnv) [LHsBinds GhcTcId]
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 InstInfo (GhcPass 'Renamed) -> TcM (LHsBinds GhcTcId)
tcInstDecl2 [InstInfo (GhcPass 'Renamed)]
inst_decls
; LHsBinds GhcTcId -> TcM (LHsBinds GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (LHsBinds GhcTcId
dm_binds LHsBinds GhcTcId -> LHsBinds GhcTcId -> LHsBinds GhcTcId
forall a. Bag a -> Bag a -> Bag a
`unionBags` [LHsBinds GhcTcId] -> LHsBinds GhcTcId
forall a. [Bag a] -> Bag a
unionManyBags [LHsBinds GhcTcId]
inst_binds_s) }
tcInstDecl2 :: InstInfo GhcRn -> TcM (LHsBinds GhcTc)
tcInstDecl2 :: InstInfo (GhcPass 'Renamed) -> TcM (LHsBinds GhcTcId)
tcInstDecl2 (InstInfo { iSpec :: forall a. InstInfo a -> ClsInst
iSpec = ClsInst
ispec, iBinds :: forall a. InstInfo a -> InstBindings a
iBinds = InstBindings (GhcPass 'Renamed)
ibinds })
= TcM (LHsBinds GhcTcId)
-> TcM (LHsBinds GhcTcId) -> TcM (LHsBinds GhcTcId)
forall r. TcRn r -> TcRn r -> TcRn r
recoverM (LHsBinds GhcTcId -> TcM (LHsBinds GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return LHsBinds GhcTcId
forall idL idR. LHsBindsLR idL idR
emptyLHsBinds) (TcM (LHsBinds GhcTcId) -> TcM (LHsBinds GhcTcId))
-> TcM (LHsBinds GhcTcId) -> TcM (LHsBinds GhcTcId)
forall a b. (a -> b) -> a -> b
$
SrcSpan -> TcM (LHsBinds GhcTcId) -> TcM (LHsBinds GhcTcId)
forall a. SrcSpan -> TcRn a -> TcRn a
setSrcSpan SrcSpan
loc (TcM (LHsBinds GhcTcId) -> TcM (LHsBinds GhcTcId))
-> TcM (LHsBinds GhcTcId) -> TcM (LHsBinds GhcTcId)
forall a b. (a -> b) -> a -> b
$
SDoc -> TcM (LHsBinds GhcTcId) -> TcM (LHsBinds GhcTcId)
forall a. SDoc -> TcM a -> TcM a
addErrCtxt (PredType -> SDoc
instDeclCtxt2 (Id -> PredType
idType Id
dfun_id)) (TcM (LHsBinds GhcTcId) -> TcM (LHsBinds GhcTcId))
-> TcM (LHsBinds GhcTcId) -> TcM (LHsBinds GhcTcId)
forall a b. (a -> b) -> a -> b
$
do {
; ([Id]
inst_tyvars, [PredType]
dfun_theta, PredType
inst_head) <- Id -> TcM ([Id], [PredType], PredType)
tcSkolDFunType Id
dfun_id
; [Id]
dfun_ev_vars <- [PredType] -> TcM [Id]
newEvVars [PredType]
dfun_theta
; let (Class
clas, [PredType]
inst_tys) = PredType -> (Class, [PredType])
tcSplitDFunHead PredType
inst_head
([Id]
class_tyvars, [PredType]
sc_theta, [Id]
_, [ClassOpItem]
op_items) = Class -> ([Id], [PredType], [Id], [ClassOpItem])
classBigSig Class
clas
sc_theta' :: [PredType]
sc_theta' = HasCallStack => TCvSubst -> [PredType] -> [PredType]
TCvSubst -> [PredType] -> [PredType]
substTheta ([Id] -> [PredType] -> TCvSubst
HasDebugCallStack => [Id] -> [PredType] -> TCvSubst
External instance of the constraint type HasDebugCallStack
zipTvSubst [Id]
class_tyvars [PredType]
inst_tys) [PredType]
sc_theta
; String -> SDoc -> TcRn ()
traceTc String
"tcInstDecl2" ([SDoc] -> SDoc
vcat [[Id] -> 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 Id
ppr [Id]
inst_tyvars, [PredType] -> 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 PredType
ppr [PredType]
inst_tys, [PredType] -> 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 PredType
ppr [PredType]
dfun_theta, [PredType] -> 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 PredType
ppr [PredType]
sc_theta'])
; spec_inst_info :: ([Located TcSpecPrag], TcPragEnv)
spec_inst_info@([Located TcSpecPrag]
spec_inst_prags,TcPragEnv
_) <- Id
-> InstBindings (GhcPass 'Renamed)
-> TcM ([Located TcSpecPrag], TcPragEnv)
tcSpecInstPrags Id
dfun_id InstBindings (GhcPass 'Renamed)
ibinds
; EvBindsVar
dfun_ev_binds_var <- TcM EvBindsVar
newTcEvBinds
; let dfun_ev_binds :: TcEvBinds
dfun_ev_binds = EvBindsVar -> TcEvBinds
TcEvBinds EvBindsVar
dfun_ev_binds_var
; (TcLevel
tclvl, ([Id]
sc_meth_ids, LHsBinds GhcTcId
sc_meth_binds, Bag Implication
sc_meth_implics))
<- TcM ([Id], LHsBinds GhcTcId, Bag Implication)
-> TcM (TcLevel, ([Id], LHsBinds GhcTcId, Bag Implication))
forall a. TcM a -> TcM (TcLevel, a)
pushTcLevelM (TcM ([Id], LHsBinds GhcTcId, Bag Implication)
-> TcM (TcLevel, ([Id], LHsBinds GhcTcId, Bag Implication)))
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication)
-> TcM (TcLevel, ([Id], LHsBinds GhcTcId, Bag Implication))
forall a b. (a -> b) -> a -> b
$
do { ([Id]
sc_ids, LHsBinds GhcTcId
sc_binds, Bag Implication
sc_implics)
<- Id
-> Class
-> [Id]
-> [Id]
-> [PredType]
-> TcEvBinds
-> [PredType]
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication)
tcSuperClasses Id
dfun_id Class
clas [Id]
inst_tyvars [Id]
dfun_ev_vars
[PredType]
inst_tys TcEvBinds
dfun_ev_binds
[PredType]
sc_theta'
; ([Id]
meth_ids, LHsBinds GhcTcId
meth_binds, Bag Implication
meth_implics)
<- Id
-> Class
-> [Id]
-> [Id]
-> [PredType]
-> TcEvBinds
-> ([Located TcSpecPrag], TcPragEnv)
-> [ClassOpItem]
-> InstBindings (GhcPass 'Renamed)
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication)
tcMethods Id
dfun_id Class
clas [Id]
inst_tyvars [Id]
dfun_ev_vars
[PredType]
inst_tys TcEvBinds
dfun_ev_binds ([Located TcSpecPrag], TcPragEnv)
spec_inst_info
[ClassOpItem]
op_items InstBindings (GhcPass 'Renamed)
ibinds
; ([Id], LHsBinds GhcTcId, Bag Implication)
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ( [Id]
sc_ids [Id] -> [Id] -> [Id]
forall a. [a] -> [a] -> [a]
++ [Id]
meth_ids
, LHsBinds GhcTcId
sc_binds LHsBinds GhcTcId -> LHsBinds GhcTcId -> LHsBinds GhcTcId
forall a. Bag a -> Bag a -> Bag a
`unionBags` LHsBinds GhcTcId
meth_binds
, Bag Implication
sc_implics Bag Implication -> Bag Implication -> Bag Implication
forall a. Bag a -> Bag a -> Bag a
`unionBags` Bag Implication
meth_implics ) }
; Implication
imp <- TcM Implication
newImplication
; Implication -> TcRn ()
emitImplication (Implication -> TcRn ()) -> Implication -> TcRn ()
forall a b. (a -> b) -> a -> b
$
Implication
imp { ic_tclvl :: TcLevel
ic_tclvl = TcLevel
tclvl
, ic_skols :: [Id]
ic_skols = [Id]
inst_tyvars
, ic_given :: [Id]
ic_given = [Id]
dfun_ev_vars
, ic_wanted :: WantedConstraints
ic_wanted = Bag Implication -> WantedConstraints
mkImplicWC Bag Implication
sc_meth_implics
, ic_binds :: EvBindsVar
ic_binds = EvBindsVar
dfun_ev_binds_var
, ic_info :: SkolemInfo
ic_info = SkolemInfo
InstSkol }
; Id
self_dict <- Class -> [PredType] -> TcM Id
newDict Class
clas [PredType]
inst_tys
; let class_tc :: TyCon
class_tc = Class -> TyCon
classTyCon Class
clas
[DataCon
dict_constr] = TyCon -> [DataCon]
tyConDataCons TyCon
class_tc
dict_bind :: LHsBind GhcTcId
dict_bind = IdP GhcTcId -> LHsExpr GhcTcId -> LHsBind GhcTcId
forall (p :: Pass).
IdP (GhcPass p) -> LHsExpr (GhcPass p) -> LHsBind (GhcPass p)
mkVarBind Id
IdP GhcTcId
self_dict (SrcSpan -> HsExpr GhcTcId -> LHsExpr GhcTcId
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc HsExpr GhcTcId
con_app_args)
con_app_tys :: HsExpr GhcTcId
con_app_tys = HsWrapper -> HsExpr GhcTcId -> HsExpr GhcTcId
mkHsWrap ([PredType] -> HsWrapper
mkWpTyApps [PredType]
inst_tys)
(XConLikeOut GhcTcId -> ConLike -> HsExpr GhcTcId
forall p. XConLikeOut p -> ConLike -> HsExpr p
HsConLikeOut XConLikeOut GhcTcId
NoExtField
noExtField (DataCon -> ConLike
RealDataCon DataCon
dict_constr))
con_app_args :: HsExpr GhcTcId
con_app_args = (HsExpr GhcTcId -> Id -> HsExpr GhcTcId)
-> HsExpr GhcTcId -> [Id] -> HsExpr GhcTcId
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldl' HsExpr GhcTcId -> Id -> HsExpr GhcTcId
app_to_meth HsExpr GhcTcId
con_app_tys [Id]
sc_meth_ids
app_to_meth :: HsExpr GhcTc -> Id -> HsExpr GhcTc
app_to_meth :: HsExpr GhcTcId -> Id -> HsExpr GhcTcId
app_to_meth HsExpr GhcTcId
fun Id
meth_id = XApp GhcTcId
-> LHsExpr GhcTcId -> LHsExpr GhcTcId -> HsExpr GhcTcId
forall p. XApp p -> LHsExpr p -> LHsExpr p -> HsExpr p
HsApp XApp GhcTcId
NoExtField
noExtField (SrcSpan -> HsExpr GhcTcId -> LHsExpr GhcTcId
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc HsExpr GhcTcId
fun)
(SrcSpan -> HsExpr GhcTcId -> LHsExpr GhcTcId
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc (HsWrapper -> Id -> HsExpr GhcTcId
wrapId HsWrapper
arg_wrapper Id
meth_id))
inst_tv_tys :: [PredType]
inst_tv_tys = [Id] -> [PredType]
mkTyVarTys [Id]
inst_tyvars
arg_wrapper :: HsWrapper
arg_wrapper = [Id] -> HsWrapper
mkWpEvVarApps [Id]
dfun_ev_vars HsWrapper -> HsWrapper -> HsWrapper
<.> [PredType] -> HsWrapper
mkWpTyApps [PredType]
inst_tv_tys
is_newtype :: Bool
is_newtype = TyCon -> Bool
isNewTyCon TyCon
class_tc
dfun_id_w_prags :: Id
dfun_id_w_prags = Id -> [Id] -> Id
addDFunPrags Id
dfun_id [Id]
sc_meth_ids
dfun_spec_prags :: TcSpecPrags
dfun_spec_prags
| Bool
is_newtype = [Located TcSpecPrag] -> TcSpecPrags
SpecPrags []
| Bool
otherwise = [Located TcSpecPrag] -> TcSpecPrags
SpecPrags [Located TcSpecPrag]
spec_inst_prags
export :: ABExport GhcTcId
export = ABE :: forall p.
XABE p -> IdP p -> IdP p -> HsWrapper -> TcSpecPrags -> ABExport p
ABE { abe_ext :: XABE GhcTcId
abe_ext = XABE GhcTcId
NoExtField
noExtField
, abe_wrap :: HsWrapper
abe_wrap = HsWrapper
idHsWrapper
, abe_poly :: IdP GhcTcId
abe_poly = Id
IdP GhcTcId
dfun_id_w_prags
, abe_mono :: IdP GhcTcId
abe_mono = Id
IdP GhcTcId
self_dict
, abe_prags :: TcSpecPrags
abe_prags = TcSpecPrags
dfun_spec_prags }
main_bind :: HsBindLR GhcTcId GhcTcId
main_bind = AbsBinds :: forall idL idR.
XAbsBinds idL idR
-> [Id]
-> [Id]
-> [ABExport idL]
-> [TcEvBinds]
-> LHsBinds idL
-> Bool
-> HsBindLR idL idR
AbsBinds { abs_ext :: XAbsBinds GhcTcId GhcTcId
abs_ext = XAbsBinds GhcTcId GhcTcId
NoExtField
noExtField
, abs_tvs :: [Id]
abs_tvs = [Id]
inst_tyvars
, abs_ev_vars :: [Id]
abs_ev_vars = [Id]
dfun_ev_vars
, abs_exports :: [ABExport GhcTcId]
abs_exports = [ABExport GhcTcId
export]
, abs_ev_binds :: [TcEvBinds]
abs_ev_binds = []
, abs_binds :: LHsBinds GhcTcId
abs_binds = LHsBind GhcTcId -> LHsBinds GhcTcId
forall a. a -> Bag a
unitBag LHsBind GhcTcId
dict_bind
, abs_sig :: Bool
abs_sig = Bool
True }
; LHsBinds GhcTcId -> TcM (LHsBinds GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (LHsBind GhcTcId -> LHsBinds GhcTcId
forall a. a -> Bag a
unitBag (SrcSpan -> HsBindLR GhcTcId GhcTcId -> LHsBind GhcTcId
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc HsBindLR GhcTcId GhcTcId
main_bind) LHsBinds GhcTcId -> LHsBinds GhcTcId -> LHsBinds GhcTcId
forall a. Bag a -> Bag a -> Bag a
`unionBags` LHsBinds GhcTcId
sc_meth_binds)
}
where
dfun_id :: Id
dfun_id = ClsInst -> Id
instanceDFunId ClsInst
ispec
loc :: SrcSpan
loc = Id -> SrcSpan
forall a. NamedThing a => a -> SrcSpan
External instance of the constraint type NamedThing Id
getSrcSpan Id
dfun_id
addDFunPrags :: DFunId -> [Id] -> DFunId
addDFunPrags :: Id -> [Id] -> Id
addDFunPrags Id
dfun_id [Id]
sc_meth_ids
| Bool
is_newtype
= Id
dfun_id Id -> Unfolding -> Id
`setIdUnfolding` ConTag -> CoreExpr -> Unfolding
mkInlineUnfoldingWithArity ConTag
0 CoreExpr
con_app
Id -> InlinePragma -> Id
`setInlinePragma` InlinePragma
alwaysInlinePragma { inl_sat :: Maybe ConTag
inl_sat = ConTag -> Maybe ConTag
forall a. a -> Maybe a
Just ConTag
0 }
| Bool
otherwise
= Id
dfun_id Id -> Unfolding -> Id
`setIdUnfolding` [Id] -> DataCon -> [CoreExpr] -> Unfolding
mkDFunUnfolding [Id]
dfun_bndrs DataCon
dict_con [CoreExpr]
dict_args
Id -> InlinePragma -> Id
`setInlinePragma` InlinePragma
dfunInlinePragma
where
con_app :: CoreExpr
con_app = [Id] -> CoreExpr -> CoreExpr
forall b. [b] -> Expr b -> Expr b
mkLams [Id]
dfun_bndrs (CoreExpr -> CoreExpr) -> CoreExpr -> CoreExpr
forall a b. (a -> b) -> a -> b
$
CoreExpr -> [CoreExpr] -> CoreExpr
forall b. Expr b -> [Expr b] -> Expr b
mkApps (Id -> CoreExpr
forall b. Id -> Expr b
Var (DataCon -> Id
dataConWrapId DataCon
dict_con)) [CoreExpr]
dict_args
dict_args :: [CoreExpr]
dict_args = (PredType -> CoreExpr) -> [PredType] -> [CoreExpr]
forall a b. (a -> b) -> [a] -> [b]
map PredType -> CoreExpr
forall b. PredType -> Expr b
Type [PredType]
inst_tys [CoreExpr] -> [CoreExpr] -> [CoreExpr]
forall a. [a] -> [a] -> [a]
++
[CoreExpr -> [Id] -> CoreExpr
forall b. Expr b -> [Id] -> Expr b
mkVarApps (Id -> CoreExpr
forall b. Id -> Expr b
Var Id
id) [Id]
dfun_bndrs | Id
id <- [Id]
sc_meth_ids]
([Id]
dfun_tvs, [PredType]
dfun_theta, Class
clas, [PredType]
inst_tys) = PredType -> ([Id], [PredType], Class, [PredType])
tcSplitDFunTy (Id -> PredType
idType Id
dfun_id)
ev_ids :: [Id]
ev_ids = ConTag -> [PredType] -> [Id]
mkTemplateLocalsNum ConTag
1 [PredType]
dfun_theta
dfun_bndrs :: [Id]
dfun_bndrs = [Id]
dfun_tvs [Id] -> [Id] -> [Id]
forall a. [a] -> [a] -> [a]
++ [Id]
ev_ids
clas_tc :: TyCon
clas_tc = Class -> TyCon
classTyCon Class
clas
[DataCon
dict_con] = TyCon -> [DataCon]
tyConDataCons TyCon
clas_tc
is_newtype :: Bool
is_newtype = TyCon -> Bool
isNewTyCon TyCon
clas_tc
wrapId :: HsWrapper -> Id -> HsExpr GhcTc
wrapId :: HsWrapper -> Id -> HsExpr GhcTcId
wrapId HsWrapper
wrapper Id
id = HsWrapper -> HsExpr GhcTcId -> HsExpr GhcTcId
mkHsWrap HsWrapper
wrapper (XVar GhcTcId -> Located (IdP GhcTcId) -> HsExpr GhcTcId
forall p. XVar p -> Located (IdP p) -> HsExpr p
HsVar XVar GhcTcId
NoExtField
noExtField (Id -> Located Id
forall e. e -> Located e
noLoc Id
id))
tcSuperClasses :: DFunId -> Class -> [TcTyVar] -> [EvVar] -> [TcType]
-> TcEvBinds
-> TcThetaType
-> TcM ([EvVar], LHsBinds GhcTc, Bag Implication)
tcSuperClasses :: Id
-> Class
-> [Id]
-> [Id]
-> [PredType]
-> TcEvBinds
-> [PredType]
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication)
tcSuperClasses Id
dfun_id Class
cls [Id]
tyvars [Id]
dfun_evs [PredType]
inst_tys TcEvBinds
dfun_ev_binds [PredType]
sc_theta
= do { ([Id]
ids, [LHsBind GhcTcId]
binds, [Implication]
implics) <- ((PredType, ConTag)
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Implication))
-> [(PredType, ConTag)]
-> IOEnv
(Env TcGblEnv TcLclEnv) ([Id], [LHsBind GhcTcId], [Implication])
forall (m :: * -> *) a b c d.
Monad m =>
(a -> m (b, c, d)) -> [a] -> m ([b], [c], [d])
External instance of the constraint type forall m. Monad (IOEnv m)
mapAndUnzip3M (PredType, ConTag)
-> IOEnv (Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Implication)
tc_super ([PredType] -> [ConTag] -> [(PredType, ConTag)]
forall a b. [a] -> [b] -> [(a, b)]
zip [PredType]
sc_theta [ConTag
fIRST_TAG..])
; ([Id], LHsBinds GhcTcId, Bag Implication)
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([Id]
ids, [LHsBind GhcTcId] -> LHsBinds GhcTcId
forall a. [a] -> Bag a
listToBag [LHsBind GhcTcId]
binds, [Implication] -> Bag Implication
forall a. [a] -> Bag a
listToBag [Implication]
implics) }
where
loc :: SrcSpan
loc = Id -> SrcSpan
forall a. NamedThing a => a -> SrcSpan
External instance of the constraint type NamedThing Id
getSrcSpan Id
dfun_id
size :: TypeSize
size = [PredType] -> TypeSize
sizeTypes [PredType]
inst_tys
tc_super :: (PredType, ConTag)
-> IOEnv (Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Implication)
tc_super (PredType
sc_pred, ConTag
n)
= do { (Implication
sc_implic, EvBindsVar
ev_binds_var, EvTerm
sc_ev_tm)
<- TcM EvTerm -> TcM (Implication, EvBindsVar, EvTerm)
forall result. TcM result -> TcM (Implication, EvBindsVar, result)
checkInstConstraints (TcM EvTerm -> TcM (Implication, EvBindsVar, EvTerm))
-> TcM EvTerm -> TcM (Implication, EvBindsVar, EvTerm)
forall a b. (a -> b) -> a -> b
$ CtOrigin -> PredType -> TcM EvTerm
emitWanted (TypeSize -> CtOrigin
ScOrigin TypeSize
size) PredType
sc_pred
; Name
sc_top_name <- OccName -> TcM Name
newName (ConTag -> OccName -> OccName
mkSuperDictAuxOcc ConTag
n (Class -> OccName
forall a. NamedThing a => a -> OccName
External instance of the constraint type NamedThing Class
getOccName Class
cls))
; Id
sc_ev_id <- PredType -> TcM Id
forall gbl lcl. PredType -> TcRnIf gbl lcl Id
newEvVar PredType
sc_pred
; EvBindsVar -> EvBind -> TcRn ()
addTcEvBind EvBindsVar
ev_binds_var (EvBind -> TcRn ()) -> EvBind -> TcRn ()
forall a b. (a -> b) -> a -> b
$ Id -> EvTerm -> EvBind
mkWantedEvBind Id
sc_ev_id EvTerm
sc_ev_tm
; let sc_top_ty :: PredType
sc_top_ty = [Id] -> PredType -> PredType
mkInfForAllTys [Id]
tyvars (PredType -> PredType) -> PredType -> PredType
forall a b. (a -> b) -> a -> b
$
[PredType] -> PredType -> PredType
mkPhiTy ((Id -> PredType) -> [Id] -> [PredType]
forall a b. (a -> b) -> [a] -> [b]
map Id -> PredType
idType [Id]
dfun_evs) PredType
sc_pred
sc_top_id :: Id
sc_top_id = HasDebugCallStack => Name -> PredType -> Id
Name -> PredType -> Id
External instance of the constraint type HasDebugCallStack
mkLocalId Name
sc_top_name PredType
sc_top_ty
export :: ABExport GhcTcId
export = ABE :: forall p.
XABE p -> IdP p -> IdP p -> HsWrapper -> TcSpecPrags -> ABExport p
ABE { abe_ext :: XABE GhcTcId
abe_ext = XABE GhcTcId
NoExtField
noExtField
, abe_wrap :: HsWrapper
abe_wrap = HsWrapper
idHsWrapper
, abe_poly :: IdP GhcTcId
abe_poly = Id
IdP GhcTcId
sc_top_id
, abe_mono :: IdP GhcTcId
abe_mono = Id
IdP GhcTcId
sc_ev_id
, abe_prags :: TcSpecPrags
abe_prags = TcSpecPrags
noSpecPrags }
local_ev_binds :: TcEvBinds
local_ev_binds = EvBindsVar -> TcEvBinds
TcEvBinds EvBindsVar
ev_binds_var
bind :: HsBindLR GhcTcId GhcTcId
bind = AbsBinds :: forall idL idR.
XAbsBinds idL idR
-> [Id]
-> [Id]
-> [ABExport idL]
-> [TcEvBinds]
-> LHsBinds idL
-> Bool
-> HsBindLR idL idR
AbsBinds { abs_ext :: XAbsBinds GhcTcId GhcTcId
abs_ext = XAbsBinds GhcTcId GhcTcId
NoExtField
noExtField
, abs_tvs :: [Id]
abs_tvs = [Id]
tyvars
, abs_ev_vars :: [Id]
abs_ev_vars = [Id]
dfun_evs
, abs_exports :: [ABExport GhcTcId]
abs_exports = [ABExport GhcTcId
export]
, abs_ev_binds :: [TcEvBinds]
abs_ev_binds = [TcEvBinds
dfun_ev_binds, TcEvBinds
local_ev_binds]
, abs_binds :: LHsBinds GhcTcId
abs_binds = LHsBinds GhcTcId
forall a. Bag a
emptyBag
, abs_sig :: Bool
abs_sig = Bool
False }
; (Id, LHsBind GhcTcId, Implication)
-> IOEnv (Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Implication)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Id
sc_top_id, SrcSpan -> HsBindLR GhcTcId GhcTcId -> LHsBind GhcTcId
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc HsBindLR GhcTcId GhcTcId
bind, Implication
sc_implic) }
checkInstConstraints :: TcM result
-> TcM (Implication, EvBindsVar, result)
checkInstConstraints :: TcM result -> TcM (Implication, EvBindsVar, result)
checkInstConstraints 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 -> TcM (TcLevel, WantedConstraints, result))
-> TcM result -> TcM (TcLevel, WantedConstraints, result)
forall a b. (a -> b) -> a -> b
$
TcM result
thing_inside
; 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_wanted :: WantedConstraints
ic_wanted = WantedConstraints
wanted
, ic_binds :: EvBindsVar
ic_binds = EvBindsVar
ev_binds_var
, ic_info :: SkolemInfo
ic_info = SkolemInfo
InstSkol }
; (Implication, EvBindsVar, result)
-> TcM (Implication, EvBindsVar, result)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Implication
implic', EvBindsVar
ev_binds_var, result
result) }
tcMethods :: DFunId -> Class
-> [TcTyVar] -> [EvVar]
-> [TcType]
-> TcEvBinds
-> ([Located TcSpecPrag], TcPragEnv)
-> [ClassOpItem]
-> InstBindings GhcRn
-> TcM ([Id], LHsBinds GhcTc, Bag Implication)
tcMethods :: Id
-> Class
-> [Id]
-> [Id]
-> [PredType]
-> TcEvBinds
-> ([Located TcSpecPrag], TcPragEnv)
-> [ClassOpItem]
-> InstBindings (GhcPass 'Renamed)
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication)
tcMethods Id
dfun_id Class
clas [Id]
tyvars [Id]
dfun_ev_vars [PredType]
inst_tys
TcEvBinds
dfun_ev_binds ([Located TcSpecPrag]
spec_inst_prags, TcPragEnv
prag_fn) [ClassOpItem]
op_items
(InstBindings { ib_binds :: forall a. InstBindings a -> LHsBinds a
ib_binds = LHsBinds (GhcPass 'Renamed)
binds
, ib_tyvars :: forall a. InstBindings a -> [Name]
ib_tyvars = [Name]
lexical_tvs
, ib_pragmas :: forall a. InstBindings a -> [LSig a]
ib_pragmas = [LSig (GhcPass 'Renamed)]
sigs
, ib_extensions :: forall a. InstBindings a -> [Extension]
ib_extensions = [Extension]
exts
, ib_derived :: forall a. InstBindings a -> Bool
ib_derived = Bool
is_derived })
= [(Name, Id)]
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication)
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication)
forall r. [(Name, Id)] -> TcM r -> TcM r
tcExtendNameTyVarEnv ([Name]
lexical_tvs [Name] -> [Id] -> [(Name, Id)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` [Id]
tyvars) (TcM ([Id], LHsBinds GhcTcId, Bag Implication)
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication))
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication)
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication)
forall a b. (a -> b) -> a -> b
$
do { String -> SDoc -> TcRn ()
traceTc String
"tcInstMeth" ([LSig (GhcPass 'Renamed)] -> 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 l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
External instance of the constraint type forall (p :: Pass).
OutputableBndrId p =>
Outputable (Sig (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 [LSig (GhcPass 'Renamed)]
sigs SDoc -> SDoc -> SDoc
$$ LHsBinds (GhcPass 'Renamed) -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable (Bag a)
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
External instance of the constraint type forall (pl :: Pass) (pr :: Pass).
(OutputableBndrId pl, OutputableBndrId pr) =>
Outputable (HsBindLR (GhcPass pl) (GhcPass pr))
External instance of the constraint type OutputableBndr Name
External instance of the constraint type OutputableBndr Name
External instance of the constraint type IsPass 'Renamed
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 LHsBinds (GhcPass 'Renamed)
binds)
; TcRn ()
checkMinimalDefinition
; TcRn ()
checkMethBindMembership
; ([Id]
ids, [LHsBind GhcTcId]
binds, [Maybe Implication]
mb_implics) <- [Extension]
-> TcM ([Id], [LHsBind GhcTcId], [Maybe Implication])
-> TcM ([Id], [LHsBind GhcTcId], [Maybe Implication])
forall a. [Extension] -> TcM a -> TcM a
set_exts [Extension]
exts (TcM ([Id], [LHsBind GhcTcId], [Maybe Implication])
-> TcM ([Id], [LHsBind GhcTcId], [Maybe Implication]))
-> TcM ([Id], [LHsBind GhcTcId], [Maybe Implication])
-> TcM ([Id], [LHsBind GhcTcId], [Maybe Implication])
forall a b. (a -> b) -> a -> b
$
TcM ([Id], [LHsBind GhcTcId], [Maybe Implication])
-> TcM ([Id], [LHsBind GhcTcId], [Maybe Implication])
forall a. TcM a -> TcM a
unset_warnings_deriving (TcM ([Id], [LHsBind GhcTcId], [Maybe Implication])
-> TcM ([Id], [LHsBind GhcTcId], [Maybe Implication]))
-> TcM ([Id], [LHsBind GhcTcId], [Maybe Implication])
-> TcM ([Id], [LHsBind GhcTcId], [Maybe Implication])
forall a b. (a -> b) -> a -> b
$
(ClassOpItem
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication))
-> [ClassOpItem]
-> TcM ([Id], [LHsBind GhcTcId], [Maybe Implication])
forall (m :: * -> *) a b c d.
Monad m =>
(a -> m (b, c, d)) -> [a] -> m ([b], [c], [d])
External instance of the constraint type forall m. Monad (IOEnv m)
mapAndUnzip3M ClassOpItem
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
tc_item [ClassOpItem]
op_items
; ([Id], LHsBinds GhcTcId, Bag Implication)
-> TcM ([Id], LHsBinds GhcTcId, Bag Implication)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([Id]
ids, [LHsBind GhcTcId] -> LHsBinds GhcTcId
forall a. [a] -> Bag a
listToBag [LHsBind GhcTcId]
binds, [Implication] -> Bag Implication
forall a. [a] -> Bag a
listToBag ([Maybe Implication] -> [Implication]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Implication]
mb_implics)) }
where
set_exts :: [LangExt.Extension] -> TcM a -> TcM a
set_exts :: [Extension] -> TcM a -> TcM a
set_exts [Extension]
es TcM a
thing = (Extension -> TcM a -> TcM a) -> TcM a -> [Extension] -> TcM a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldr Extension -> TcM a -> TcM a
forall gbl lcl a. Extension -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
setXOptM TcM a
thing [Extension]
es
unset_warnings_deriving :: TcM a -> TcM a
unset_warnings_deriving :: TcM a -> TcM a
unset_warnings_deriving
| Bool
is_derived = WarningFlag -> TcM a -> TcM a
forall gbl lcl a.
WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
unsetWOptM WarningFlag
Opt_WarnInaccessibleCode
| Bool
otherwise = TcM a -> TcM a
forall a. a -> a
id
hs_sig_fn :: HsSigFun
hs_sig_fn = [LSig (GhcPass 'Renamed)] -> HsSigFun
mkHsSigFun [LSig (GhcPass 'Renamed)]
sigs
inst_loc :: SrcSpan
inst_loc = Id -> SrcSpan
forall a. NamedThing a => a -> SrcSpan
External instance of the constraint type NamedThing Id
getSrcSpan Id
dfun_id
tc_item :: ClassOpItem -> TcM (Id, LHsBind GhcTc, Maybe Implication)
tc_item :: ClassOpItem
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
tc_item (Id
sel_id, DefMethInfo
dm_info)
| Just (GenLocated SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
user_bind, SrcSpan
bndr_loc, [LSig (GhcPass 'Renamed)]
prags) <- Name
-> LHsBinds (GhcPass 'Renamed)
-> TcPragEnv
-> Maybe
(GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)),
SrcSpan, [LSig (GhcPass 'Renamed)])
findMethodBind (Id -> Name
idName Id
sel_id) LHsBinds (GhcPass 'Renamed)
binds TcPragEnv
prag_fn
= Class
-> [Id]
-> [Id]
-> [PredType]
-> TcEvBinds
-> Bool
-> HsSigFun
-> [Located TcSpecPrag]
-> [LSig (GhcPass 'Renamed)]
-> Id
-> GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
-> SrcSpan
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
tcMethodBody Class
clas [Id]
tyvars [Id]
dfun_ev_vars [PredType]
inst_tys
TcEvBinds
dfun_ev_binds Bool
is_derived HsSigFun
hs_sig_fn
[Located TcSpecPrag]
spec_inst_prags [LSig (GhcPass 'Renamed)]
prags
Id
sel_id GenLocated SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
user_bind SrcSpan
bndr_loc
| Bool
otherwise
= do { String -> SDoc -> TcRn ()
traceTc String
"tc_def" (Id -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Id
ppr Id
sel_id)
; Id
-> DefMethInfo
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
tc_default Id
sel_id DefMethInfo
dm_info }
tc_default :: Id -> DefMethInfo
-> TcM (TcId, LHsBind GhcTc, Maybe Implication)
tc_default :: Id
-> DefMethInfo
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
tc_default Id
sel_id (Just (Name
dm_name, DefMethSpec PredType
_))
= do { (GenLocated SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
meth_bind, [LSig (GhcPass 'Renamed)]
inline_prags) <- Class
-> [PredType]
-> Id
-> Name
-> TcM
(GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)),
[LSig (GhcPass 'Renamed)])
mkDefMethBind Class
clas [PredType]
inst_tys Id
sel_id Name
dm_name
; Class
-> [Id]
-> [Id]
-> [PredType]
-> TcEvBinds
-> Bool
-> HsSigFun
-> [Located TcSpecPrag]
-> [LSig (GhcPass 'Renamed)]
-> Id
-> GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
-> SrcSpan
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
tcMethodBody Class
clas [Id]
tyvars [Id]
dfun_ev_vars [PredType]
inst_tys
TcEvBinds
dfun_ev_binds Bool
is_derived HsSigFun
hs_sig_fn
[Located TcSpecPrag]
spec_inst_prags [LSig (GhcPass 'Renamed)]
inline_prags
Id
sel_id GenLocated SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
meth_bind SrcSpan
inst_loc }
tc_default Id
sel_id DefMethInfo
Nothing
= do { String -> SDoc -> TcRn ()
traceTc String
"tc_def: warn" (Id -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Id
ppr Id
sel_id)
; (Id
meth_id, Id
_) <- Class -> [Id] -> [Id] -> [PredType] -> Id -> TcM (Id, Id)
mkMethIds Class
clas [Id]
tyvars [Id]
dfun_ev_vars
[PredType]
inst_tys Id
sel_id
; 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 meth_bind :: LHsBind GhcTcId
meth_bind = IdP GhcTcId -> LHsExpr GhcTcId -> LHsBind GhcTcId
forall (p :: Pass).
IdP (GhcPass p) -> LHsExpr (GhcPass p) -> LHsBind (GhcPass p)
mkVarBind Id
IdP GhcTcId
meth_id (LHsExpr GhcTcId -> LHsBind GhcTcId)
-> LHsExpr GhcTcId -> LHsBind GhcTcId
forall a b. (a -> b) -> a -> b
$
HsWrapper -> LHsExpr GhcTcId -> LHsExpr GhcTcId
mkLHsWrap HsWrapper
lam_wrapper (DynFlags -> LHsExpr GhcTcId
error_rhs DynFlags
dflags)
; (Id, LHsBind GhcTcId, Maybe Implication)
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Id
meth_id, LHsBind GhcTcId
meth_bind, Maybe Implication
forall a. Maybe a
Nothing) }
where
error_rhs :: DynFlags -> LHsExpr GhcTcId
error_rhs DynFlags
dflags = SrcSpan -> HsExpr GhcTcId -> LHsExpr GhcTcId
forall l e. l -> e -> GenLocated l e
L SrcSpan
inst_loc (HsExpr GhcTcId -> LHsExpr GhcTcId)
-> HsExpr GhcTcId -> LHsExpr GhcTcId
forall a b. (a -> b) -> a -> b
$ XApp GhcTcId
-> LHsExpr GhcTcId -> LHsExpr GhcTcId -> HsExpr GhcTcId
forall p. XApp p -> LHsExpr p -> LHsExpr p -> HsExpr p
HsApp XApp GhcTcId
NoExtField
noExtField LHsExpr GhcTcId
error_fun (DynFlags -> LHsExpr GhcTcId
error_msg DynFlags
dflags)
error_fun :: LHsExpr GhcTcId
error_fun = SrcSpan -> HsExpr GhcTcId -> LHsExpr GhcTcId
forall l e. l -> e -> GenLocated l e
L SrcSpan
inst_loc (HsExpr GhcTcId -> LHsExpr GhcTcId)
-> HsExpr GhcTcId -> LHsExpr GhcTcId
forall a b. (a -> b) -> a -> b
$
HsWrapper -> Id -> HsExpr GhcTcId
wrapId ([PredType] -> HsWrapper
mkWpTyApps
[ HasDebugCallStack => PredType -> PredType
PredType -> PredType
External instance of the constraint type HasDebugCallStack
getRuntimeRep PredType
meth_tau, PredType
meth_tau])
Id
nO_METHOD_BINDING_ERROR_ID
error_msg :: DynFlags -> LHsExpr GhcTcId
error_msg DynFlags
dflags = SrcSpan -> HsExpr GhcTcId -> LHsExpr GhcTcId
forall l e. l -> e -> GenLocated l e
L SrcSpan
inst_loc (XLitE GhcTcId -> HsLit GhcTcId -> HsExpr GhcTcId
forall p. XLitE p -> HsLit p -> HsExpr p
HsLit XLitE GhcTcId
NoExtField
noExtField (XHsStringPrim GhcTcId -> ByteString -> HsLit GhcTcId
forall x. XHsStringPrim x -> ByteString -> HsLit x
HsStringPrim SourceText
XHsStringPrim GhcTcId
NoSourceText
(String -> ByteString
unsafeMkByteString (DynFlags -> String
error_string DynFlags
dflags))))
meth_tau :: PredType
meth_tau = PredType -> PredType
funResultTy (HasDebugCallStack => PredType -> [PredType] -> PredType
PredType -> [PredType] -> PredType
External instance of the constraint type HasDebugCallStack
piResultTys (Id -> PredType
idType Id
sel_id) [PredType]
inst_tys)
error_string :: DynFlags -> String
error_string DynFlags
dflags = DynFlags -> SDoc -> String
showSDoc DynFlags
dflags
([SDoc] -> SDoc
hcat [SrcSpan -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable SrcSpan
ppr SrcSpan
inst_loc, SDoc
vbar, Id -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Id
ppr Id
sel_id ])
lam_wrapper :: HsWrapper
lam_wrapper = [Id] -> HsWrapper
mkWpTyLams [Id]
tyvars HsWrapper -> HsWrapper -> HsWrapper
<.> [Id] -> HsWrapper
mkWpLams [Id]
dfun_ev_vars
checkMinimalDefinition :: TcRn ()
checkMinimalDefinition
= Maybe (BooleanFormula Name)
-> (BooleanFormula Name -> TcRn ()) -> TcRn ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
External instance of the constraint type forall m. Monad (IOEnv m)
whenIsJust ((Name -> Bool)
-> BooleanFormula Name -> Maybe (BooleanFormula Name)
forall a.
Eq a =>
(a -> Bool) -> BooleanFormula a -> Maybe (BooleanFormula a)
External instance of the constraint type Eq Name
isUnsatisfied Name -> Bool
methodExists (Class -> BooleanFormula Name
classMinimalDef Class
clas)) ((BooleanFormula Name -> TcRn ()) -> TcRn ())
-> (BooleanFormula Name -> TcRn ()) -> TcRn ()
forall a b. (a -> b) -> a -> b
$
BooleanFormula Name -> TcRn ()
warnUnsatisfiedMinimalDefinition
methodExists :: Name -> Bool
methodExists Name
meth = Maybe
(GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)),
SrcSpan, [LSig (GhcPass 'Renamed)])
-> Bool
forall a. Maybe a -> Bool
isJust (Name
-> LHsBinds (GhcPass 'Renamed)
-> TcPragEnv
-> Maybe
(GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)),
SrcSpan, [LSig (GhcPass 'Renamed)])
findMethodBind Name
meth LHsBinds (GhcPass 'Renamed)
binds TcPragEnv
prag_fn)
checkMethBindMembership :: TcRn ()
checkMethBindMembership
= (Name -> TcRn ()) -> [Name] -> TcRn ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
External instance of the constraint type forall m. Monad (IOEnv m)
External instance of the constraint type Foldable []
mapM_ (SDoc -> TcRn ()
addErrTc (SDoc -> TcRn ()) -> (Name -> SDoc) -> Name -> TcRn ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Class -> Name -> SDoc
forall a. Outputable a => a -> Name -> SDoc
External instance of the constraint type Outputable Class
badMethodErr Class
clas) [Name]
mismatched_meths
where
bind_nms :: [Name]
bind_nms = (GenLocated SrcSpan Name -> Name)
-> [GenLocated SrcSpan Name] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map GenLocated SrcSpan Name -> Name
forall l e. GenLocated l e -> e
unLoc ([GenLocated SrcSpan Name] -> [Name])
-> [GenLocated SrcSpan Name] -> [Name]
forall a b. (a -> b) -> a -> b
$ LHsBinds (GhcPass 'Renamed) -> [Located (IdP (GhcPass 'Renamed))]
forall idL idR. LHsBindsLR idL idR -> [Located (IdP idL)]
collectMethodBinders LHsBinds (GhcPass 'Renamed)
binds
cls_meth_nms :: [Name]
cls_meth_nms = (ClassOpItem -> Name) -> [ClassOpItem] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map (Id -> Name
idName (Id -> Name) -> (ClassOpItem -> Id) -> ClassOpItem -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ClassOpItem -> Id
forall a b. (a, b) -> a
fst) [ClassOpItem]
op_items
mismatched_meths :: [Name]
mismatched_meths = [Name]
bind_nms [Name] -> [Name] -> [Name]
forall a. Ord a => [a] -> [a] -> [a]
External instance of the constraint type Ord Name
`minusList` [Name]
cls_meth_nms
tcMethodBody :: Class -> [TcTyVar] -> [EvVar] -> [TcType]
-> TcEvBinds -> Bool
-> HsSigFun
-> [LTcSpecPrag] -> [LSig GhcRn]
-> Id -> LHsBind GhcRn -> SrcSpan
-> TcM (TcId, LHsBind GhcTc, Maybe Implication)
tcMethodBody :: Class
-> [Id]
-> [Id]
-> [PredType]
-> TcEvBinds
-> Bool
-> HsSigFun
-> [Located TcSpecPrag]
-> [LSig (GhcPass 'Renamed)]
-> Id
-> GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
-> SrcSpan
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
tcMethodBody Class
clas [Id]
tyvars [Id]
dfun_ev_vars [PredType]
inst_tys
TcEvBinds
dfun_ev_binds Bool
is_derived
HsSigFun
sig_fn [Located TcSpecPrag]
spec_inst_prags [LSig (GhcPass 'Renamed)]
prags
Id
sel_id (L SrcSpan
bind_loc HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)
meth_bind) SrcSpan
bndr_loc
= IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
add_meth_ctxt (IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication))
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
forall a b. (a -> b) -> a -> b
$
do { String -> SDoc -> TcRn ()
traceTc String
"tcMethodBody" (Id -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Id
ppr Id
sel_id SDoc -> SDoc -> SDoc
<+> PredType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable PredType
ppr (Id -> PredType
idType Id
sel_id) SDoc -> SDoc -> SDoc
$$ SrcSpan -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable SrcSpan
ppr SrcSpan
bndr_loc)
; (Id
global_meth_id, Id
local_meth_id) <- SrcSpan -> TcM (Id, Id) -> TcM (Id, Id)
forall a. SrcSpan -> TcRn a -> TcRn a
setSrcSpan SrcSpan
bndr_loc (TcM (Id, Id) -> TcM (Id, Id)) -> TcM (Id, Id) -> TcM (Id, Id)
forall a b. (a -> b) -> a -> b
$
Class -> [Id] -> [Id] -> [PredType] -> Id -> TcM (Id, Id)
mkMethIds Class
clas [Id]
tyvars [Id]
dfun_ev_vars
[PredType]
inst_tys Id
sel_id
; let lm_bind :: HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)
lm_bind = HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)
meth_bind { fun_id :: Located (IdP (GhcPass 'Renamed))
fun_id = SrcSpan -> Name -> GenLocated SrcSpan Name
forall l e. l -> e -> GenLocated l e
L SrcSpan
bndr_loc (Id -> Name
idName Id
local_meth_id) }
; (Implication
meth_implic, EvBindsVar
ev_binds_var, LHsBinds GhcTcId
tc_bind)
<- TcM (LHsBinds GhcTcId)
-> TcM (Implication, EvBindsVar, LHsBinds GhcTcId)
forall result. TcM result -> TcM (Implication, EvBindsVar, result)
checkInstConstraints (TcM (LHsBinds GhcTcId)
-> TcM (Implication, EvBindsVar, LHsBinds GhcTcId))
-> TcM (LHsBinds GhcTcId)
-> TcM (Implication, EvBindsVar, LHsBinds GhcTcId)
forall a b. (a -> b) -> a -> b
$
HsSigFun
-> Id
-> Id
-> GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
-> TcM (LHsBinds GhcTcId)
tcMethodBodyHelp HsSigFun
sig_fn Id
sel_id Id
local_meth_id (SrcSpan
-> HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)
-> GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
forall l e. l -> e -> GenLocated l e
L SrcSpan
bind_loc HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)
lm_bind)
; Id
global_meth_id <- Id -> [LSig (GhcPass 'Renamed)] -> TcM Id
addInlinePrags Id
global_meth_id [LSig (GhcPass 'Renamed)]
prags
; [Located TcSpecPrag]
spec_prags <- Id -> [LSig (GhcPass 'Renamed)] -> TcM [Located TcSpecPrag]
tcSpecPrags Id
global_meth_id [LSig (GhcPass 'Renamed)]
prags
; let specs :: TcSpecPrags
specs = Id -> [Located TcSpecPrag] -> [Located TcSpecPrag] -> TcSpecPrags
mk_meth_spec_prags Id
global_meth_id [Located TcSpecPrag]
spec_inst_prags [Located TcSpecPrag]
spec_prags
export :: ABExport GhcTcId
export = ABE :: forall p.
XABE p -> IdP p -> IdP p -> HsWrapper -> TcSpecPrags -> ABExport p
ABE { abe_ext :: XABE GhcTcId
abe_ext = XABE GhcTcId
NoExtField
noExtField
, abe_poly :: IdP GhcTcId
abe_poly = Id
IdP GhcTcId
global_meth_id
, abe_mono :: IdP GhcTcId
abe_mono = Id
IdP GhcTcId
local_meth_id
, abe_wrap :: HsWrapper
abe_wrap = HsWrapper
idHsWrapper
, abe_prags :: TcSpecPrags
abe_prags = TcSpecPrags
specs }
local_ev_binds :: TcEvBinds
local_ev_binds = EvBindsVar -> TcEvBinds
TcEvBinds EvBindsVar
ev_binds_var
full_bind :: HsBindLR GhcTcId GhcTcId
full_bind = AbsBinds :: forall idL idR.
XAbsBinds idL idR
-> [Id]
-> [Id]
-> [ABExport idL]
-> [TcEvBinds]
-> LHsBinds idL
-> Bool
-> HsBindLR idL idR
AbsBinds { abs_ext :: XAbsBinds GhcTcId GhcTcId
abs_ext = XAbsBinds GhcTcId GhcTcId
NoExtField
noExtField
, abs_tvs :: [Id]
abs_tvs = [Id]
tyvars
, abs_ev_vars :: [Id]
abs_ev_vars = [Id]
dfun_ev_vars
, abs_exports :: [ABExport GhcTcId]
abs_exports = [ABExport GhcTcId
export]
, abs_ev_binds :: [TcEvBinds]
abs_ev_binds = [TcEvBinds
dfun_ev_binds, TcEvBinds
local_ev_binds]
, abs_binds :: LHsBinds GhcTcId
abs_binds = LHsBinds GhcTcId
tc_bind
, abs_sig :: Bool
abs_sig = Bool
True }
; (Id, LHsBind GhcTcId, Maybe Implication)
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Id
global_meth_id, SrcSpan -> HsBindLR GhcTcId GhcTcId -> LHsBind GhcTcId
forall l e. l -> e -> GenLocated l e
L SrcSpan
bind_loc HsBindLR GhcTcId GhcTcId
full_bind, Implication -> Maybe Implication
forall a. a -> Maybe a
Just Implication
meth_implic) }
where
add_meth_ctxt :: IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
add_meth_ctxt IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
thing
| Bool
is_derived = SDoc
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
-> IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
forall a. SDoc -> TcM a -> TcM a
addLandmarkErrCtxt (Id -> Class -> [PredType] -> SDoc
derivBindCtxt Id
sel_id Class
clas [PredType]
inst_tys) IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
thing
| Bool
otherwise = IOEnv
(Env TcGblEnv TcLclEnv) (Id, LHsBind GhcTcId, Maybe Implication)
thing
tcMethodBodyHelp :: HsSigFun -> Id -> TcId
-> LHsBind GhcRn -> TcM (LHsBinds GhcTcId)
tcMethodBodyHelp :: HsSigFun
-> Id
-> Id
-> GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
-> TcM (LHsBinds GhcTcId)
tcMethodBodyHelp HsSigFun
hs_sig_fn Id
sel_id Id
local_meth_id GenLocated SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
meth_bind
| Just LHsSigType (GhcPass 'Renamed)
hs_sig_ty <- HsSigFun
hs_sig_fn Name
sel_name
= do { (PredType
sig_ty, HsWrapper
hs_wrap)
<- SrcSpan -> TcRn (PredType, HsWrapper) -> TcRn (PredType, HsWrapper)
forall a. SrcSpan -> TcRn a -> TcRn a
setSrcSpan (LHsType (GhcPass 'Renamed) -> SrcSpan
forall l e. GenLocated l e -> l
getLoc (LHsSigType (GhcPass 'Renamed) -> LHsType (GhcPass 'Renamed)
forall (p :: Pass). LHsSigType (GhcPass p) -> LHsType (GhcPass p)
hsSigType LHsSigType (GhcPass 'Renamed)
hs_sig_ty)) (TcRn (PredType, HsWrapper) -> TcRn (PredType, HsWrapper))
-> TcRn (PredType, HsWrapper) -> TcRn (PredType, HsWrapper)
forall a b. (a -> b) -> a -> b
$
do { Bool
inst_sigs <- Extension -> TcRn Bool
forall gbl lcl. Extension -> TcRnIf gbl lcl Bool
xoptM Extension
LangExt.InstanceSigs
; Bool -> SDoc -> TcRn ()
checkTc Bool
inst_sigs (Name -> LHsSigType (GhcPass 'Renamed) -> SDoc
misplacedInstSig Name
sel_name LHsSigType (GhcPass 'Renamed)
hs_sig_ty)
; PredType
sig_ty <- UserTypeCtxt -> LHsSigType (GhcPass 'Renamed) -> TcM PredType
tcHsSigType (Name -> Bool -> UserTypeCtxt
FunSigCtxt Name
sel_name Bool
False) LHsSigType (GhcPass 'Renamed)
hs_sig_ty
; let local_meth_ty :: PredType
local_meth_ty = Id -> PredType
idType Id
local_meth_id
ctxt :: UserTypeCtxt
ctxt = Name -> Bool -> UserTypeCtxt
FunSigCtxt Name
sel_name Bool
False
; HsWrapper
hs_wrap <- (TidyEnv -> TcM (TidyEnv, SDoc)) -> TcM HsWrapper -> TcM HsWrapper
forall a. (TidyEnv -> TcM (TidyEnv, SDoc)) -> TcM a -> TcM a
addErrCtxtM (Name -> PredType -> PredType -> TidyEnv -> TcM (TidyEnv, SDoc)
methSigCtxt Name
sel_name PredType
sig_ty PredType
local_meth_ty) (TcM HsWrapper -> TcM HsWrapper) -> TcM HsWrapper -> TcM HsWrapper
forall a b. (a -> b) -> a -> b
$
UserTypeCtxt -> PredType -> PredType -> TcM HsWrapper
tcSubType_NC UserTypeCtxt
ctxt PredType
sig_ty PredType
local_meth_ty
; (PredType, HsWrapper) -> TcRn (PredType, HsWrapper)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (PredType
sig_ty, HsWrapper
hs_wrap) }
; Name
inner_meth_name <- OccName -> TcM Name
newName (Name -> OccName
nameOccName Name
sel_name)
; let ctxt :: UserTypeCtxt
ctxt = Name -> Bool -> UserTypeCtxt
FunSigCtxt Name
sel_name Bool
True
inner_meth_id :: Id
inner_meth_id = HasDebugCallStack => Name -> PredType -> Id
Name -> PredType -> Id
External instance of the constraint type HasDebugCallStack
mkLocalId Name
inner_meth_name PredType
sig_ty
inner_meth_sig :: TcIdSigInfo
inner_meth_sig = CompleteSig :: Id -> UserTypeCtxt -> SrcSpan -> TcIdSigInfo
CompleteSig { sig_bndr :: Id
sig_bndr = Id
inner_meth_id
, sig_ctxt :: UserTypeCtxt
sig_ctxt = UserTypeCtxt
ctxt
, sig_loc :: SrcSpan
sig_loc = LHsType (GhcPass 'Renamed) -> SrcSpan
forall l e. GenLocated l e -> l
getLoc (LHsSigType (GhcPass 'Renamed) -> LHsType (GhcPass 'Renamed)
forall (p :: Pass). LHsSigType (GhcPass p) -> LHsType (GhcPass p)
hsSigType LHsSigType (GhcPass 'Renamed)
hs_sig_ty) }
; (LHsBinds GhcTcId
tc_bind, [Id
inner_id]) <- TcPragEnv
-> TcIdSigInfo
-> GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
-> TcM (LHsBinds GhcTcId, [Id])
tcPolyCheck TcPragEnv
no_prag_fn TcIdSigInfo
inner_meth_sig GenLocated SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
meth_bind
; let export :: ABExport GhcTcId
export = ABE :: forall p.
XABE p -> IdP p -> IdP p -> HsWrapper -> TcSpecPrags -> ABExport p
ABE { abe_ext :: XABE GhcTcId
abe_ext = XABE GhcTcId
NoExtField
noExtField
, abe_poly :: IdP GhcTcId
abe_poly = Id
IdP GhcTcId
local_meth_id
, abe_mono :: IdP GhcTcId
abe_mono = Id
IdP GhcTcId
inner_id
, abe_wrap :: HsWrapper
abe_wrap = HsWrapper
hs_wrap
, abe_prags :: TcSpecPrags
abe_prags = TcSpecPrags
noSpecPrags }
; LHsBinds GhcTcId -> TcM (LHsBinds GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (LHsBind GhcTcId -> LHsBinds GhcTcId
forall a. a -> Bag a
unitBag (LHsBind GhcTcId -> LHsBinds GhcTcId)
-> LHsBind GhcTcId -> LHsBinds GhcTcId
forall a b. (a -> b) -> a -> b
$ SrcSpan -> HsBindLR GhcTcId GhcTcId -> LHsBind GhcTcId
forall l e. l -> e -> GenLocated l e
L (GenLocated SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
-> SrcSpan
forall l e. GenLocated l e -> l
getLoc GenLocated SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
meth_bind) (HsBindLR GhcTcId GhcTcId -> LHsBind GhcTcId)
-> HsBindLR GhcTcId GhcTcId -> LHsBind GhcTcId
forall a b. (a -> b) -> a -> b
$
AbsBinds :: forall idL idR.
XAbsBinds idL idR
-> [Id]
-> [Id]
-> [ABExport idL]
-> [TcEvBinds]
-> LHsBinds idL
-> Bool
-> HsBindLR idL idR
AbsBinds { abs_ext :: XAbsBinds GhcTcId GhcTcId
abs_ext = XAbsBinds GhcTcId GhcTcId
NoExtField
noExtField, abs_tvs :: [Id]
abs_tvs = [], abs_ev_vars :: [Id]
abs_ev_vars = []
, abs_exports :: [ABExport GhcTcId]
abs_exports = [ABExport GhcTcId
export]
, abs_binds :: LHsBinds GhcTcId
abs_binds = LHsBinds GhcTcId
tc_bind, abs_ev_binds :: [TcEvBinds]
abs_ev_binds = []
, abs_sig :: Bool
abs_sig = Bool
True }) }
| Bool
otherwise
= do { let ctxt :: UserTypeCtxt
ctxt = Name -> Bool -> UserTypeCtxt
FunSigCtxt Name
sel_name Bool
False
tc_sig :: TcIdSigInfo
tc_sig = UserTypeCtxt -> Id -> TcIdSigInfo
completeSigFromId UserTypeCtxt
ctxt Id
local_meth_id
; (LHsBinds GhcTcId
tc_bind, [Id]
_) <- TcPragEnv
-> TcIdSigInfo
-> GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
-> TcM (LHsBinds GhcTcId, [Id])
tcPolyCheck TcPragEnv
no_prag_fn TcIdSigInfo
tc_sig GenLocated SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
meth_bind
; LHsBinds GhcTcId -> TcM (LHsBinds GhcTcId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return LHsBinds GhcTcId
tc_bind }
where
sel_name :: Name
sel_name = Id -> Name
idName Id
sel_id
no_prag_fn :: TcPragEnv
no_prag_fn = TcPragEnv
emptyPragEnv
mkMethIds :: Class -> [TcTyVar] -> [EvVar]
-> [TcType] -> Id -> TcM (TcId, TcId)
mkMethIds :: Class -> [Id] -> [Id] -> [PredType] -> Id -> TcM (Id, Id)
mkMethIds Class
clas [Id]
tyvars [Id]
dfun_ev_vars [PredType]
inst_tys Id
sel_id
= do { Name
poly_meth_name <- OccName -> TcM Name
newName (OccName -> OccName
mkClassOpAuxOcc OccName
sel_occ)
; Name
local_meth_name <- OccName -> TcM Name
newName OccName
sel_occ
; let poly_meth_id :: Id
poly_meth_id = HasDebugCallStack => Name -> PredType -> Id
Name -> PredType -> Id
External instance of the constraint type HasDebugCallStack
mkLocalId Name
poly_meth_name PredType
poly_meth_ty
local_meth_id :: Id
local_meth_id = HasDebugCallStack => Name -> PredType -> Id
Name -> PredType -> Id
External instance of the constraint type HasDebugCallStack
mkLocalId Name
local_meth_name PredType
local_meth_ty
; (Id, Id) -> TcM (Id, Id)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Id
poly_meth_id, Id
local_meth_id) }
where
sel_name :: Name
sel_name = Id -> Name
idName Id
sel_id
sel_occ :: OccName
sel_occ = Name -> OccName
nameOccName Name
sel_name
local_meth_ty :: PredType
local_meth_ty = Class -> Id -> [PredType] -> PredType
instantiateMethod Class
clas Id
sel_id [PredType]
inst_tys
poly_meth_ty :: PredType
poly_meth_ty = [Id] -> [PredType] -> PredType -> PredType
mkSpecSigmaTy [Id]
tyvars [PredType]
theta PredType
local_meth_ty
theta :: [PredType]
theta = (Id -> PredType) -> [Id] -> [PredType]
forall a b. (a -> b) -> [a] -> [b]
map Id -> PredType
idType [Id]
dfun_ev_vars
methSigCtxt :: Name -> TcType -> TcType -> TidyEnv -> TcM (TidyEnv, MsgDoc)
methSigCtxt :: Name -> PredType -> PredType -> TidyEnv -> TcM (TidyEnv, SDoc)
methSigCtxt Name
sel_name PredType
sig_ty PredType
meth_ty TidyEnv
env0
= do { (TidyEnv
env1, PredType
sig_ty) <- TidyEnv -> PredType -> TcM (TidyEnv, PredType)
zonkTidyTcType TidyEnv
env0 PredType
sig_ty
; (TidyEnv
env2, PredType
meth_ty) <- TidyEnv -> PredType -> TcM (TidyEnv, PredType)
zonkTidyTcType TidyEnv
env1 PredType
meth_ty
; let msg :: SDoc
msg = SDoc -> ConTag -> SDoc -> SDoc
hang (String -> SDoc
text String
"When checking that instance signature for" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (Name -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Name
ppr Name
sel_name))
ConTag
2 ([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"is more general than its signature in the class"
, String -> SDoc
text String
"Instance sig:" SDoc -> SDoc -> SDoc
<+> PredType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable PredType
ppr PredType
sig_ty
, String -> SDoc
text String
" Class sig:" SDoc -> SDoc -> SDoc
<+> PredType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable PredType
ppr PredType
meth_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
env2, SDoc
msg) }
misplacedInstSig :: Name -> LHsSigType GhcRn -> SDoc
misplacedInstSig :: Name -> LHsSigType (GhcPass 'Renamed) -> SDoc
misplacedInstSig Name
name LHsSigType (GhcPass 'Renamed)
hs_ty
= [SDoc] -> SDoc
vcat [ SDoc -> ConTag -> SDoc -> SDoc
hang (String -> SDoc
text String
"Illegal type signature in instance declaration:")
ConTag
2 (SDoc -> ConTag -> SDoc -> SDoc
hang (Name -> SDoc
forall a. NamedThing a => a -> SDoc
External instance of the constraint type NamedThing Name
pprPrefixName Name
name)
ConTag
2 (SDoc
dcolon SDoc -> SDoc -> SDoc
<+> LHsSigType (GhcPass 'Renamed) -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall thing (p :: Pass).
Outputable thing =>
Outputable (HsImplicitBndrs (GhcPass p) thing)
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
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 LHsSigType (GhcPass 'Renamed)
hs_ty))
, String -> SDoc
text String
"(Use InstanceSigs to allow this)" ]
mk_meth_spec_prags :: Id -> [LTcSpecPrag] -> [LTcSpecPrag] -> TcSpecPrags
mk_meth_spec_prags :: Id -> [Located TcSpecPrag] -> [Located TcSpecPrag] -> TcSpecPrags
mk_meth_spec_prags Id
meth_id [Located TcSpecPrag]
spec_inst_prags [Located TcSpecPrag]
spec_prags_for_me
= [Located TcSpecPrag] -> TcSpecPrags
SpecPrags ([Located TcSpecPrag]
spec_prags_for_me [Located TcSpecPrag]
-> [Located TcSpecPrag] -> [Located TcSpecPrag]
forall a. [a] -> [a] -> [a]
++ [Located TcSpecPrag]
spec_prags_from_inst)
where
spec_prags_from_inst :: [Located TcSpecPrag]
spec_prags_from_inst
| InlinePragma -> Bool
isInlinePragma (Id -> InlinePragma
idInlinePragma Id
meth_id)
= []
| Bool
otherwise
= [ SrcSpan -> TcSpecPrag -> Located TcSpecPrag
forall l e. l -> e -> GenLocated l e
L SrcSpan
inst_loc (Id -> HsWrapper -> InlinePragma -> TcSpecPrag
SpecPrag Id
meth_id HsWrapper
wrap InlinePragma
inl)
| L SrcSpan
inst_loc (SpecPrag Id
_ HsWrapper
wrap InlinePragma
inl) <- [Located TcSpecPrag]
spec_inst_prags]
mkDefMethBind :: Class -> [Type] -> Id -> Name
-> TcM (LHsBind GhcRn, [LSig GhcRn])
mkDefMethBind :: Class
-> [PredType]
-> Id
-> Name
-> TcM
(GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)),
[LSig (GhcPass 'Renamed)])
mkDefMethBind Class
clas [PredType]
inst_tys Id
sel_id Name
dm_name
= 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
; Id
dm_id <- Name -> TcM Id
tcLookupId Name
dm_name
; let inline_prag :: InlinePragma
inline_prag = Id -> InlinePragma
idInlinePragma Id
dm_id
inline_prags :: [LSig (GhcPass 'Renamed)]
inline_prags | InlinePragma -> Bool
isAnyInlinePragma InlinePragma
inline_prag
= [Sig (GhcPass 'Renamed) -> LSig (GhcPass 'Renamed)
forall e. e -> Located e
noLoc (XInlineSig (GhcPass 'Renamed)
-> Located (IdP (GhcPass 'Renamed))
-> InlinePragma
-> Sig (GhcPass 'Renamed)
forall pass.
XInlineSig pass -> Located (IdP pass) -> InlinePragma -> Sig pass
InlineSig XInlineSig (GhcPass 'Renamed)
NoExtField
noExtField GenLocated SrcSpan Name
Located (IdP (GhcPass 'Renamed))
fn InlinePragma
inline_prag)]
| Bool
otherwise
= []
fn :: GenLocated SrcSpan Name
fn = Name -> GenLocated SrcSpan Name
forall e. e -> Located e
noLoc (Id -> Name
idName Id
sel_id)
visible_inst_tys :: [PredType]
visible_inst_tys = [ PredType
ty | (TyConBinder
tcb, PredType
ty) <- TyCon -> [TyConBinder]
tyConBinders (Class -> TyCon
classTyCon Class
clas) [TyConBinder] -> [PredType] -> [(TyConBinder, PredType)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` [PredType]
inst_tys
, TyConBinder -> ArgFlag
tyConBinderArgFlag TyConBinder
tcb ArgFlag -> ArgFlag -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq ArgFlag
/= ArgFlag
Inferred ]
rhs :: LHsExpr (GhcPass 'Renamed)
rhs = (LHsExpr (GhcPass 'Renamed)
-> PredType -> LHsExpr (GhcPass 'Renamed))
-> LHsExpr (GhcPass 'Renamed)
-> [PredType]
-> LHsExpr (GhcPass 'Renamed)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldl' LHsExpr (GhcPass 'Renamed)
-> PredType -> LHsExpr (GhcPass 'Renamed)
mk_vta (IdP (GhcPass 'Renamed) -> LHsExpr (GhcPass 'Renamed)
forall (id :: Pass). IdP (GhcPass id) -> LHsExpr (GhcPass id)
nlHsVar Name
IdP (GhcPass 'Renamed)
dm_name) [PredType]
visible_inst_tys
bind :: GenLocated SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
bind = HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)
-> GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
forall e. e -> Located e
noLoc (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)
-> GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)))
-> HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)
-> GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
forall a b. (a -> b) -> a -> b
$ Origin
-> GenLocated SrcSpan Name
-> [LMatch (GhcPass 'Renamed) (LHsExpr (GhcPass 'Renamed))]
-> HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)
mkTopFunBind Origin
Generated GenLocated SrcSpan Name
fn ([LMatch (GhcPass 'Renamed) (LHsExpr (GhcPass 'Renamed))]
-> HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
-> [LMatch (GhcPass 'Renamed) (LHsExpr (GhcPass 'Renamed))]
-> HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)
forall a b. (a -> b) -> a -> b
$
[HsMatchContext (NoGhcTc (GhcPass 'Renamed))
-> [LPat (GhcPass 'Renamed)]
-> LHsExpr (GhcPass 'Renamed)
-> LMatch (GhcPass 'Renamed) (LHsExpr (GhcPass 'Renamed))
forall (p :: Pass) (body :: * -> *).
HsMatchContext (NoGhcTc (GhcPass p))
-> [LPat (GhcPass p)]
-> Located (body (GhcPass p))
-> LMatch (GhcPass p) (Located (body (GhcPass p)))
mkSimpleMatch (Located (IdP (GhcPass 'Renamed))
-> HsMatchContext (GhcPass 'Renamed)
forall p. LIdP p -> HsMatchContext p
mkPrefixFunRhs GenLocated SrcSpan Name
Located (IdP (GhcPass 'Renamed))
fn) [] LHsExpr (GhcPass 'Renamed)
rhs]
; IO () -> TcRn ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall env. MonadIO (IOEnv env)
liftIO (DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_deriv String
"Filling in method body"
DumpFormat
FormatHaskell
([SDoc] -> SDoc
vcat [Class -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Class
ppr Class
clas SDoc -> SDoc -> SDoc
<+> [PredType] -> 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 PredType
ppr [PredType]
inst_tys,
ConTag -> SDoc -> SDoc
nest ConTag
2 (Id -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Id
ppr Id
sel_id SDoc -> SDoc -> SDoc
<+> SDoc
equals SDoc -> SDoc -> SDoc
<+> LHsExpr (GhcPass 'Renamed) -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
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 LHsExpr (GhcPass 'Renamed)
rhs)]))
; (GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)),
[LSig (GhcPass 'Renamed)])
-> TcM
(GenLocated
SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed)),
[LSig (GhcPass 'Renamed)])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (GenLocated SrcSpan (HsBindLR (GhcPass 'Renamed) (GhcPass 'Renamed))
bind, [LSig (GhcPass 'Renamed)]
inline_prags) }
where
mk_vta :: LHsExpr GhcRn -> Type -> LHsExpr GhcRn
mk_vta :: LHsExpr (GhcPass 'Renamed)
-> PredType -> LHsExpr (GhcPass 'Renamed)
mk_vta LHsExpr (GhcPass 'Renamed)
fun PredType
ty = HsExpr (GhcPass 'Renamed) -> LHsExpr (GhcPass 'Renamed)
forall e. e -> Located e
noLoc (XAppTypeE (GhcPass 'Renamed)
-> LHsExpr (GhcPass 'Renamed)
-> LHsWcType (NoGhcTc (GhcPass 'Renamed))
-> HsExpr (GhcPass 'Renamed)
forall p.
XAppTypeE p -> LHsExpr p -> LHsWcType (NoGhcTc p) -> HsExpr p
HsAppType XAppTypeE (GhcPass 'Renamed)
NoExtField
noExtField LHsExpr (GhcPass 'Renamed)
fun (LHsType (GhcPass 'Renamed)
-> HsWildCardBndrs (GhcPass 'Renamed) (LHsType (GhcPass 'Renamed))
forall thing. thing -> HsWildCardBndrs (GhcPass 'Renamed) thing
mkEmptyWildCardBndrs (LHsType (GhcPass 'Renamed)
-> HsWildCardBndrs (GhcPass 'Renamed) (LHsType (GhcPass 'Renamed)))
-> LHsType (GhcPass 'Renamed)
-> HsWildCardBndrs (GhcPass 'Renamed) (LHsType (GhcPass 'Renamed))
forall a b. (a -> b) -> a -> b
$ LHsType (GhcPass 'Renamed) -> LHsType (GhcPass 'Renamed)
forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p)
nlHsParTy
(LHsType (GhcPass 'Renamed) -> LHsType (GhcPass 'Renamed))
-> LHsType (GhcPass 'Renamed) -> LHsType (GhcPass 'Renamed)
forall a b. (a -> b) -> a -> b
$ HsType (GhcPass 'Renamed) -> LHsType (GhcPass 'Renamed)
forall e. e -> Located e
noLoc (HsType (GhcPass 'Renamed) -> LHsType (GhcPass 'Renamed))
-> HsType (GhcPass 'Renamed) -> LHsType (GhcPass 'Renamed)
forall a b. (a -> b) -> a -> b
$ XXType (GhcPass 'Renamed) -> HsType (GhcPass 'Renamed)
forall pass. XXType pass -> HsType pass
XHsType (XXType (GhcPass 'Renamed) -> HsType (GhcPass 'Renamed))
-> XXType (GhcPass 'Renamed) -> HsType (GhcPass 'Renamed)
forall a b. (a -> b) -> a -> b
$ PredType -> NewHsTypeX
NHsCoreTy PredType
ty))
derivBindCtxt :: Id -> Class -> [Type ] -> SDoc
derivBindCtxt :: Id -> Class -> [PredType] -> SDoc
derivBindCtxt Id
sel_id Class
clas [PredType]
tys
= [SDoc] -> SDoc
vcat [ String -> SDoc
text String
"When typechecking the code for" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (Id -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Id
ppr Id
sel_id)
, ConTag -> SDoc -> SDoc
nest ConTag
2 (String -> SDoc
text String
"in a derived instance for"
SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (Class -> [PredType] -> SDoc
pprClassPred Class
clas [PredType]
tys) SDoc -> SDoc -> SDoc
<> SDoc
colon)
, ConTag -> SDoc -> SDoc
nest ConTag
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"To see the code I am typechecking, use -ddump-deriv" ]
warnUnsatisfiedMinimalDefinition :: ClassMinimalDef -> TcM ()
warnUnsatisfiedMinimalDefinition :: BooleanFormula Name -> TcRn ()
warnUnsatisfiedMinimalDefinition BooleanFormula Name
mindef
= do { Bool
warn <- WarningFlag -> TcRn Bool
forall gbl lcl. WarningFlag -> TcRnIf gbl lcl Bool
woptM WarningFlag
Opt_WarnMissingMethods
; WarnReason -> Bool -> SDoc -> TcRn ()
warnTc (WarningFlag -> WarnReason
Reason WarningFlag
Opt_WarnMissingMethods) Bool
warn SDoc
message
}
where
message :: SDoc
message = [SDoc] -> SDoc
vcat [String -> SDoc
text String
"No explicit implementation for"
,ConTag -> SDoc -> SDoc
nest ConTag
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ BooleanFormula Name -> SDoc
forall a. Outputable a => BooleanFormula a -> SDoc
External instance of the constraint type Outputable Name
pprBooleanFormulaNice BooleanFormula Name
mindef
]
tcSpecInstPrags :: DFunId -> InstBindings GhcRn
-> TcM ([Located TcSpecPrag], TcPragEnv)
tcSpecInstPrags :: Id
-> InstBindings (GhcPass 'Renamed)
-> TcM ([Located TcSpecPrag], TcPragEnv)
tcSpecInstPrags Id
dfun_id (InstBindings { ib_binds :: forall a. InstBindings a -> LHsBinds a
ib_binds = LHsBinds (GhcPass 'Renamed)
binds, ib_pragmas :: forall a. InstBindings a -> [LSig a]
ib_pragmas = [LSig (GhcPass 'Renamed)]
uprags })
= do { [Located TcSpecPrag]
spec_inst_prags <- (LSig (GhcPass 'Renamed)
-> IOEnv (Env TcGblEnv TcLclEnv) (Located TcSpecPrag))
-> [LSig (GhcPass 'Renamed)] -> TcM [Located TcSpecPrag]
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 ((Sig (GhcPass 'Renamed) -> TcM TcSpecPrag)
-> LSig (GhcPass 'Renamed)
-> IOEnv (Env TcGblEnv TcLclEnv) (Located TcSpecPrag)
forall a b. (a -> TcM b) -> Located a -> TcM (Located b)
wrapLocM (Id -> Sig (GhcPass 'Renamed) -> TcM TcSpecPrag
tcSpecInst Id
dfun_id)) ([LSig (GhcPass 'Renamed)] -> TcM [Located TcSpecPrag])
-> [LSig (GhcPass 'Renamed)] -> TcM [Located TcSpecPrag]
forall a b. (a -> b) -> a -> b
$
(LSig (GhcPass 'Renamed) -> Bool)
-> [LSig (GhcPass 'Renamed)] -> [LSig (GhcPass 'Renamed)]
forall a. (a -> Bool) -> [a] -> [a]
filter LSig (GhcPass 'Renamed) -> Bool
forall name. LSig name -> Bool
isSpecInstLSig [LSig (GhcPass 'Renamed)]
uprags
; ([Located TcSpecPrag], TcPragEnv)
-> TcM ([Located TcSpecPrag], TcPragEnv)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return ([Located TcSpecPrag]
spec_inst_prags, [LSig (GhcPass 'Renamed)]
-> LHsBinds (GhcPass 'Renamed) -> TcPragEnv
mkPragEnv [LSig (GhcPass 'Renamed)]
uprags LHsBinds (GhcPass 'Renamed)
binds) }
tcSpecInst :: Id -> Sig GhcRn -> TcM TcSpecPrag
tcSpecInst :: Id -> Sig (GhcPass 'Renamed) -> TcM TcSpecPrag
tcSpecInst Id
dfun_id prag :: Sig (GhcPass 'Renamed)
prag@(SpecInstSig XSpecInstSig (GhcPass 'Renamed)
_ SourceText
_ LHsSigType (GhcPass 'Renamed)
hs_ty)
= SDoc -> TcM TcSpecPrag -> TcM TcSpecPrag
forall a. SDoc -> TcM a -> TcM a
addErrCtxt (Sig (GhcPass 'Renamed) -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall (p :: Pass).
OutputableBndrId p =>
Outputable (Sig (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
spec_ctxt Sig (GhcPass 'Renamed)
prag) (TcM TcSpecPrag -> TcM TcSpecPrag)
-> TcM TcSpecPrag -> TcM TcSpecPrag
forall a b. (a -> b) -> a -> b
$
do { PredType
spec_dfun_ty <- UserTypeCtxt -> LHsSigType (GhcPass 'Renamed) -> TcM PredType
tcHsClsInstType UserTypeCtxt
SpecInstCtxt LHsSigType (GhcPass 'Renamed)
hs_ty
; HsWrapper
co_fn <- UserTypeCtxt -> PredType -> PredType -> TcM HsWrapper
tcSpecWrapper UserTypeCtxt
SpecInstCtxt (Id -> PredType
idType Id
dfun_id) PredType
spec_dfun_ty
; TcSpecPrag -> TcM TcSpecPrag
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall m. Monad (IOEnv m)
return (Id -> HsWrapper -> InlinePragma -> TcSpecPrag
SpecPrag Id
dfun_id HsWrapper
co_fn InlinePragma
defaultInlinePragma) }
where
spec_ctxt :: a -> SDoc
spec_ctxt a
prag = SDoc -> ConTag -> SDoc -> SDoc
hang (String -> SDoc
text String
"In the pragma:") ConTag
2 (a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable a
ppr a
prag)
tcSpecInst Id
_ Sig (GhcPass 'Renamed)
_ = String -> TcM TcSpecPrag
forall a. String -> a
panic String
"tcSpecInst"
instDeclCtxt1 :: LHsSigType GhcRn -> SDoc
instDeclCtxt1 :: LHsSigType (GhcPass 'Renamed) -> SDoc
instDeclCtxt1 LHsSigType (GhcPass 'Renamed)
hs_inst_ty
= SDoc -> SDoc
inst_decl_ctxt (LHsType (GhcPass 'Renamed) -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
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 (LHsSigType (GhcPass 'Renamed) -> LHsType (GhcPass 'Renamed)
forall (p :: Pass). LHsSigType (GhcPass p) -> LHsType (GhcPass p)
getLHsInstDeclHead LHsSigType (GhcPass 'Renamed)
hs_inst_ty))
instDeclCtxt2 :: Type -> SDoc
instDeclCtxt2 :: PredType -> SDoc
instDeclCtxt2 PredType
dfun_ty
= SDoc -> SDoc
inst_decl_ctxt (PredType -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable PredType
ppr (Class -> [PredType] -> PredType
mkClassPred Class
cls [PredType]
tys))
where
([Id]
_,[PredType]
_,Class
cls,[PredType]
tys) = PredType -> ([Id], [PredType], Class, [PredType])
tcSplitDFunTy PredType
dfun_ty
inst_decl_ctxt :: SDoc -> SDoc
inst_decl_ctxt :: SDoc -> SDoc
inst_decl_ctxt SDoc
doc = SDoc -> ConTag -> SDoc -> SDoc
hang (String -> SDoc
text String
"In the instance declaration for")
ConTag
2 (SDoc -> SDoc
quotes SDoc
doc)
badBootFamInstDeclErr :: SDoc
badBootFamInstDeclErr :: SDoc
badBootFamInstDeclErr
= String -> SDoc
text String
"Illegal family instance in hs-boot file"
notFamily :: TyCon -> SDoc
notFamily :: TyCon -> SDoc
notFamily TyCon
tycon
= [SDoc] -> SDoc
vcat [ String -> SDoc
text String
"Illegal family instance for" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (TyCon -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TyCon
ppr TyCon
tycon)
, ConTag -> SDoc -> SDoc
nest ConTag
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> SDoc
parens (TyCon -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TyCon
ppr TyCon
tycon SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"is not an indexed type family")]
assocInClassErr :: TyCon -> SDoc
assocInClassErr :: TyCon -> SDoc
assocInClassErr TyCon
name
= String -> SDoc
text String
"Associated type" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (TyCon -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TyCon
ppr TyCon
name) SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"must be inside a class instance"
badFamInstDecl :: TyCon -> SDoc
badFamInstDecl :: TyCon -> SDoc
badFamInstDecl TyCon
tc_name
= [SDoc] -> SDoc
vcat [ String -> SDoc
text String
"Illegal family instance for" SDoc -> SDoc -> SDoc
<+>
SDoc -> SDoc
quotes (TyCon -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TyCon
ppr TyCon
tc_name)
, ConTag -> SDoc -> SDoc
nest ConTag
2 (SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"Use TypeFamilies to allow indexed type families") ]
notOpenFamily :: TyCon -> SDoc
notOpenFamily :: TyCon -> SDoc
notOpenFamily TyCon
tc
= String -> SDoc
text String
"Illegal instance for closed family" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (TyCon -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TyCon
ppr TyCon
tc)