{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
{-# LANGUAGE ParallelListComp #-}
module GHC.Tc.Errors(
reportUnsolved, reportAllUnsolved, warnAllUnsolved,
warnDefaulting,
solverReportMsg_ExpectedActuals,
solverReportInfo_ExpectedActuals
) where
import GHC.Prelude
import GHC.Driver.Env (hsc_units)
import GHC.Driver.Session
import GHC.Driver.Ppr
import GHC.Driver.Config.Diagnostic
import GHC.Rename.Unbound
import GHC.Tc.Types
import GHC.Tc.Utils.Monad
import GHC.Tc.Errors.Types
import GHC.Tc.Errors.Ppr
import GHC.Tc.Types.Constraint
import GHC.Tc.Utils.TcMType
import GHC.Tc.Utils.Env( tcInitTidyEnv )
import GHC.Tc.Utils.TcType
import GHC.Tc.Utils.Unify ( checkTyVarEq )
import GHC.Tc.Types.Origin
import GHC.Tc.Types.Evidence
import GHC.Tc.Types.EvTerm
import GHC.Tc.Instance.Family
import GHC.Tc.Utils.Instantiate
import {-# SOURCE #-} GHC.Tc.Errors.Hole ( findValidHoleFits, getHoleFitDispConfig, pprHoleFit )
import GHC.Types.Name
import GHC.Types.Name.Reader ( lookupGRE_Name, GlobalRdrEnv, mkRdrUnqual
, emptyLocalRdrEnv, lookupGlobalRdrEnv , lookupLocalRdrOcc )
import GHC.Types.Id
import GHC.Types.Var
import GHC.Types.Var.Set
import GHC.Types.Var.Env
import GHC.Types.Name.Env
import GHC.Types.SrcLoc
import GHC.Types.Basic
import GHC.Types.Error
import qualified GHC.Types.Unique.Map as UM
import GHC.Unit.Module
import qualified GHC.LanguageExtensions as LangExt
import GHC.Core.Predicate
import GHC.Core.Type
import GHC.Core.Coercion
import GHC.Core.TyCo.Ppr ( pprTyVars
)
import GHC.Core.InstEnv
import GHC.Core.TyCon
import GHC.Core.DataCon
import GHC.Utils.Error (diagReasonSeverity, pprLocMsgEnvelope )
import GHC.Utils.Misc
import GHC.Utils.Outputable as O
import GHC.Utils.Panic
import GHC.Utils.Panic.Plain
import GHC.Utils.FV ( fvVarList, unionFV )
import GHC.Data.Bag
import GHC.Data.List.SetOps ( equivClasses, nubOrdBy )
import GHC.Data.Maybe
import qualified GHC.Data.Strict as Strict
import Control.Monad ( unless, when, foldM, forM_ )
import Data.Foldable ( toList )
import Data.Function ( on )
import Data.List ( partition, sort, sortBy )
import Data.List.NonEmpty ( NonEmpty(..), (<|) )
import qualified Data.List.NonEmpty as NE ( map, reverse )
import Data.Ord ( comparing )
import qualified Data.Semigroup as S
reportUnsolved :: WantedConstraints -> TcM (Bag EvBind)
reportUnsolved :: WantedConstraints -> TcM (Bag EvBind)
reportUnsolved WantedConstraints
wanted
= do { EvBindsVar
binds_var <- TcM EvBindsVar
newTcEvBinds
; Bool
defer_errors <- forall gbl lcl. GeneralFlag -> TcRnIf gbl lcl Bool
goptM GeneralFlag
Opt_DeferTypeErrors
; let type_errors :: DiagnosticReason
type_errors | Bool -> Bool
not Bool
defer_errors = DiagnosticReason
ErrorWithoutFlag
| Bool
otherwise = WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnDeferredTypeErrors
; Bool
defer_holes <- forall gbl lcl. GeneralFlag -> TcRnIf gbl lcl Bool
goptM GeneralFlag
Opt_DeferTypedHoles
; let expr_holes :: DiagnosticReason
expr_holes | Bool -> Bool
not Bool
defer_holes = DiagnosticReason
ErrorWithoutFlag
| Bool
otherwise = WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnTypedHoles
; Bool
partial_sigs <- forall gbl lcl. Extension -> TcRnIf gbl lcl Bool
xoptM Extension
LangExt.PartialTypeSignatures
; let type_holes :: DiagnosticReason
type_holes | Bool -> Bool
not Bool
partial_sigs
= DiagnosticReason
ErrorWithoutFlag
| Bool
otherwise
= WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnPartialTypeSignatures
; Bool
defer_out_of_scope <- forall gbl lcl. GeneralFlag -> TcRnIf gbl lcl Bool
goptM GeneralFlag
Opt_DeferOutOfScopeVariables
; let out_of_scope_holes :: DiagnosticReason
out_of_scope_holes | Bool -> Bool
not Bool
defer_out_of_scope
= DiagnosticReason
ErrorWithoutFlag
| Bool
otherwise
= WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnDeferredOutOfScopeVariables
; DiagnosticReason
-> DiagnosticReason
-> DiagnosticReason
-> DiagnosticReason
-> EvBindsVar
-> WantedConstraints
-> TcM ()
report_unsolved DiagnosticReason
type_errors DiagnosticReason
expr_holes
DiagnosticReason
type_holes DiagnosticReason
out_of_scope_holes
EvBindsVar
binds_var WantedConstraints
wanted
; EvBindMap
ev_binds <- EvBindsVar -> TcM EvBindMap
getTcEvBindsMap EvBindsVar
binds_var
; forall (m :: * -> *) a. Monad m => a -> m a
return (EvBindMap -> Bag EvBind
evBindMapBinds EvBindMap
ev_binds)}
reportAllUnsolved :: WantedConstraints -> TcM ()
reportAllUnsolved :: WantedConstraints -> TcM ()
reportAllUnsolved WantedConstraints
wanted
= do { EvBindsVar
ev_binds <- TcM EvBindsVar
newNoTcEvBinds
; Bool
partial_sigs <- forall gbl lcl. Extension -> TcRnIf gbl lcl Bool
xoptM Extension
LangExt.PartialTypeSignatures
; let type_holes :: DiagnosticReason
type_holes | Bool -> Bool
not Bool
partial_sigs = DiagnosticReason
ErrorWithoutFlag
| Bool
otherwise = WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnPartialTypeSignatures
; DiagnosticReason
-> DiagnosticReason
-> DiagnosticReason
-> DiagnosticReason
-> EvBindsVar
-> WantedConstraints
-> TcM ()
report_unsolved DiagnosticReason
ErrorWithoutFlag
DiagnosticReason
ErrorWithoutFlag DiagnosticReason
type_holes DiagnosticReason
ErrorWithoutFlag
EvBindsVar
ev_binds WantedConstraints
wanted }
warnAllUnsolved :: WantedConstraints -> TcM ()
warnAllUnsolved :: WantedConstraints -> TcM ()
warnAllUnsolved WantedConstraints
wanted
= do { EvBindsVar
ev_binds <- TcM EvBindsVar
newTcEvBinds
; DiagnosticReason
-> DiagnosticReason
-> DiagnosticReason
-> DiagnosticReason
-> EvBindsVar
-> WantedConstraints
-> TcM ()
report_unsolved DiagnosticReason
WarningWithoutFlag
DiagnosticReason
WarningWithoutFlag
DiagnosticReason
WarningWithoutFlag
DiagnosticReason
WarningWithoutFlag
EvBindsVar
ev_binds WantedConstraints
wanted }
report_unsolved :: DiagnosticReason
-> DiagnosticReason
-> DiagnosticReason
-> DiagnosticReason
-> EvBindsVar
-> WantedConstraints -> TcM ()
report_unsolved :: DiagnosticReason
-> DiagnosticReason
-> DiagnosticReason
-> DiagnosticReason
-> EvBindsVar
-> WantedConstraints
-> TcM ()
report_unsolved DiagnosticReason
type_errors DiagnosticReason
expr_holes
DiagnosticReason
type_holes DiagnosticReason
out_of_scope_holes EvBindsVar
binds_var WantedConstraints
wanted
| WantedConstraints -> Bool
isEmptyWC WantedConstraints
wanted
= forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise
= do { String -> SDoc -> TcM ()
traceTc String
"reportUnsolved {" forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat [ String -> SDoc
text String
"type errors:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr DiagnosticReason
type_errors
, String -> SDoc
text String
"expr holes:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr DiagnosticReason
expr_holes
, String -> SDoc
text String
"type holes:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr DiagnosticReason
type_holes
, String -> SDoc
text String
"scope holes:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr DiagnosticReason
out_of_scope_holes ]
; String -> SDoc -> TcM ()
traceTc String
"reportUnsolved (before zonking and tidying)" (forall a. Outputable a => a -> SDoc
ppr WantedConstraints
wanted)
; WantedConstraints
wanted <- WantedConstraints -> TcM WantedConstraints
zonkWC WantedConstraints
wanted
; let tidy_env :: TidyEnv
tidy_env = TidyEnv -> [TcId] -> TidyEnv
tidyFreeTyCoVars TidyEnv
emptyTidyEnv [TcId]
free_tvs
free_tvs :: [TcId]
free_tvs = forall a. (a -> Bool) -> [a] -> [a]
filterOut TcId -> Bool
isCoVar forall a b. (a -> b) -> a -> b
$
WantedConstraints -> [TcId]
tyCoVarsOfWCList WantedConstraints
wanted
; String -> SDoc -> TcM ()
traceTc String
"reportUnsolved (after zonking):" forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat [ String -> SDoc
text String
"Free tyvars:" SDoc -> SDoc -> SDoc
<+> [TcId] -> SDoc
pprTyVars [TcId]
free_tvs
, String -> SDoc
text String
"Tidy env:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr TidyEnv
tidy_env
, String -> SDoc
text String
"Wanted:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr WantedConstraints
wanted ]
; Bool
warn_redundant <- forall gbl lcl. WarningFlag -> TcRnIf gbl lcl Bool
woptM WarningFlag
Opt_WarnRedundantConstraints
; Bool
exp_syns <- forall gbl lcl. GeneralFlag -> TcRnIf gbl lcl Bool
goptM GeneralFlag
Opt_PrintExpandedSynonyms
; let err_ctxt :: SolverReportErrCtxt
err_ctxt = CEC { cec_encl :: [Implication]
cec_encl = []
, cec_tidy :: TidyEnv
cec_tidy = TidyEnv
tidy_env
, cec_defer_type_errors :: DiagnosticReason
cec_defer_type_errors = DiagnosticReason
type_errors
, cec_expr_holes :: DiagnosticReason
cec_expr_holes = DiagnosticReason
expr_holes
, cec_type_holes :: DiagnosticReason
cec_type_holes = DiagnosticReason
type_holes
, cec_out_of_scope_holes :: DiagnosticReason
cec_out_of_scope_holes = DiagnosticReason
out_of_scope_holes
, cec_suppress :: Bool
cec_suppress = WantedConstraints -> Bool
insolubleWC WantedConstraints
wanted
, cec_warn_redundant :: Bool
cec_warn_redundant = Bool
warn_redundant
, cec_expand_syns :: Bool
cec_expand_syns = Bool
exp_syns
, cec_binds :: EvBindsVar
cec_binds = EvBindsVar
binds_var }
; TcLevel
tc_lvl <- TcM TcLevel
getTcLevel
; SolverReportErrCtxt -> TcLevel -> WantedConstraints -> TcM ()
reportWanteds SolverReportErrCtxt
err_ctxt TcLevel
tc_lvl WantedConstraints
wanted
; String -> SDoc -> TcM ()
traceTc String
"reportUnsolved }" SDoc
empty }
important :: SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important :: SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt TcSolverReportMsg
doc = forall a. Monoid a => a
mempty { sr_important_msgs :: [SolverReportWithCtxt]
sr_important_msgs = [SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt TcSolverReportMsg
doc] }
mk_relevant_bindings :: RelevantBindings -> SolverReport
mk_relevant_bindings :: RelevantBindings -> SolverReport
mk_relevant_bindings RelevantBindings
binds = forall a. Monoid a => a
mempty { sr_supplementary :: [SolverReportSupplementary]
sr_supplementary = [RelevantBindings -> SolverReportSupplementary
SupplementaryBindings RelevantBindings
binds] }
mk_report_hints :: [GhcHint] -> SolverReport
mk_report_hints :: [GhcHint] -> SolverReport
mk_report_hints [GhcHint]
hints = forall a. Monoid a => a
mempty { sr_hints :: [GhcHint]
sr_hints = [GhcHint]
hints }
deferringAnyBindings :: SolverReportErrCtxt -> Bool
deferringAnyBindings :: SolverReportErrCtxt -> Bool
deferringAnyBindings (CEC { cec_defer_type_errors :: SolverReportErrCtxt -> DiagnosticReason
cec_defer_type_errors = DiagnosticReason
ErrorWithoutFlag
, cec_expr_holes :: SolverReportErrCtxt -> DiagnosticReason
cec_expr_holes = DiagnosticReason
ErrorWithoutFlag
, cec_out_of_scope_holes :: SolverReportErrCtxt -> DiagnosticReason
cec_out_of_scope_holes = DiagnosticReason
ErrorWithoutFlag }) = Bool
False
deferringAnyBindings SolverReportErrCtxt
_ = Bool
True
maybeSwitchOffDefer :: EvBindsVar -> SolverReportErrCtxt -> SolverReportErrCtxt
maybeSwitchOffDefer :: EvBindsVar -> SolverReportErrCtxt -> SolverReportErrCtxt
maybeSwitchOffDefer EvBindsVar
evb SolverReportErrCtxt
ctxt
| CoEvBindsVar{} <- EvBindsVar
evb
= SolverReportErrCtxt
ctxt { cec_defer_type_errors :: DiagnosticReason
cec_defer_type_errors = DiagnosticReason
ErrorWithoutFlag
, cec_expr_holes :: DiagnosticReason
cec_expr_holes = DiagnosticReason
ErrorWithoutFlag
, cec_out_of_scope_holes :: DiagnosticReason
cec_out_of_scope_holes = DiagnosticReason
ErrorWithoutFlag }
| Bool
otherwise
= SolverReportErrCtxt
ctxt
reportImplic :: SolverReportErrCtxt -> Implication -> TcM ()
reportImplic :: SolverReportErrCtxt -> Implication -> TcM ()
reportImplic SolverReportErrCtxt
ctxt implic :: Implication
implic@(Implic { ic_skols :: Implication -> [TcId]
ic_skols = [TcId]
tvs
, ic_given :: Implication -> [TcId]
ic_given = [TcId]
given
, ic_wanted :: Implication -> WantedConstraints
ic_wanted = WantedConstraints
wanted, ic_binds :: Implication -> EvBindsVar
ic_binds = EvBindsVar
evb
, ic_status :: Implication -> ImplicStatus
ic_status = ImplicStatus
status, ic_info :: Implication -> SkolemInfoAnon
ic_info = SkolemInfoAnon
info
, ic_env :: Implication -> TcLclEnv
ic_env = TcLclEnv
tcl_env
, ic_tclvl :: Implication -> TcLevel
ic_tclvl = TcLevel
tc_lvl })
| SkolemInfoAnon
BracketSkol <- SkolemInfoAnon
info
, Bool -> Bool
not Bool
insoluble
= forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise
= do { String -> SDoc -> TcM ()
traceTc String
"reportImplic" forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat
[ String -> SDoc
text String
"tidy env:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr (SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt)
, String -> SDoc
text String
"skols: " SDoc -> SDoc -> SDoc
<+> [TcId] -> SDoc
pprTyVars [TcId]
tvs
, String -> SDoc
text String
"tidy skols:" SDoc -> SDoc -> SDoc
<+> [TcId] -> SDoc
pprTyVars [TcId]
tvs' ]
; forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
bad_telescope forall a b. (a -> b) -> a -> b
$ SolverReportErrCtxt
-> TcLclEnv -> SkolemInfoAnon -> [TcId] -> TcM ()
reportBadTelescope SolverReportErrCtxt
ctxt TcLclEnv
tcl_env SkolemInfoAnon
info [TcId]
tvs
; SolverReportErrCtxt -> TcLevel -> WantedConstraints -> TcM ()
reportWanteds SolverReportErrCtxt
ctxt' TcLevel
tc_lvl WantedConstraints
wanted
; forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (SolverReportErrCtxt -> Bool
cec_warn_redundant SolverReportErrCtxt
ctxt) forall a b. (a -> b) -> a -> b
$
SolverReportErrCtxt
-> TcLclEnv -> SkolemInfoAnon -> [TcId] -> TcM ()
warnRedundantConstraints SolverReportErrCtxt
ctxt' TcLclEnv
tcl_env SkolemInfoAnon
info' [TcId]
dead_givens }
where
insoluble :: Bool
insoluble = ImplicStatus -> Bool
isInsolubleStatus ImplicStatus
status
(TidyEnv
env1, [TcId]
tvs') = TidyEnv -> [TcId] -> (TidyEnv, [TcId])
tidyVarBndrs (SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt) forall a b. (a -> b) -> a -> b
$
[TcId] -> [TcId]
scopedSort [TcId]
tvs
info' :: SkolemInfoAnon
info' = TidyEnv -> SkolemInfoAnon -> SkolemInfoAnon
tidySkolemInfoAnon TidyEnv
env1 SkolemInfoAnon
info
implic' :: Implication
implic' = Implication
implic { ic_skols :: [TcId]
ic_skols = [TcId]
tvs'
, ic_given :: [TcId]
ic_given = forall a b. (a -> b) -> [a] -> [b]
map (TidyEnv -> TcId -> TcId
tidyEvVar TidyEnv
env1) [TcId]
given
, ic_info :: SkolemInfoAnon
ic_info = SkolemInfoAnon
info' }
ctxt1 :: SolverReportErrCtxt
ctxt1 = EvBindsVar -> SolverReportErrCtxt -> SolverReportErrCtxt
maybeSwitchOffDefer EvBindsVar
evb SolverReportErrCtxt
ctxt
ctxt' :: SolverReportErrCtxt
ctxt' = SolverReportErrCtxt
ctxt1 { cec_tidy :: TidyEnv
cec_tidy = TidyEnv
env1
, cec_encl :: [Implication]
cec_encl = Implication
implic' forall a. a -> [a] -> [a]
: SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt
, cec_suppress :: Bool
cec_suppress = Bool
insoluble Bool -> Bool -> Bool
|| SolverReportErrCtxt -> Bool
cec_suppress SolverReportErrCtxt
ctxt
, cec_binds :: EvBindsVar
cec_binds = EvBindsVar
evb }
dead_givens :: [TcId]
dead_givens = case ImplicStatus
status of
IC_Solved { ics_dead :: ImplicStatus -> [TcId]
ics_dead = [TcId]
dead } -> [TcId]
dead
ImplicStatus
_ -> []
bad_telescope :: Bool
bad_telescope = case ImplicStatus
status of
ImplicStatus
IC_BadTelescope -> Bool
True
ImplicStatus
_ -> Bool
False
warnRedundantConstraints :: SolverReportErrCtxt -> TcLclEnv -> SkolemInfoAnon -> [EvVar] -> TcM ()
warnRedundantConstraints :: SolverReportErrCtxt
-> TcLclEnv -> SkolemInfoAnon -> [TcId] -> TcM ()
warnRedundantConstraints SolverReportErrCtxt
ctxt TcLclEnv
env SkolemInfoAnon
info [TcId]
ev_vars
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TcId]
redundant_evs
= forall (m :: * -> *) a. Monad m => a -> m a
return ()
| SigSkol UserTypeCtxt
user_ctxt Type
_ [(Name, TcId)]
_ <- SkolemInfoAnon
info
= forall gbl a.
TcLclEnv -> TcRnIf gbl TcLclEnv a -> TcRnIf gbl TcLclEnv a
restoreLclEnv TcLclEnv
env forall a b. (a -> b) -> a -> b
$
forall a. SrcSpan -> TcRn a -> TcRn a
setSrcSpan (UserTypeCtxt -> SrcSpan
redundantConstraintsSpan UserTypeCtxt
user_ctxt) forall a b. (a -> b) -> a -> b
$
Bool -> TcM ()
report_redundant_msg Bool
True
| Bool
otherwise
= forall gbl a.
TcLclEnv -> TcRnIf gbl TcLclEnv a -> TcRnIf gbl TcLclEnv a
restoreLclEnv TcLclEnv
env
forall a b. (a -> b) -> a -> b
$ Bool -> TcM ()
report_redundant_msg Bool
False
where
report_redundant_msg :: Bool
-> TcRn ()
report_redundant_msg :: Bool -> TcM ()
report_redundant_msg Bool
show_info
= do { TcLclEnv
lcl_env <- forall gbl lcl. TcRnIf gbl lcl lcl
getLclEnv
; MsgEnvelope TcRnMessage
msg <-
TcLclEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport
TcLclEnv
lcl_env
([TcId] -> (SkolemInfoAnon, Bool) -> TcRnMessage
TcRnRedundantConstraints [TcId]
redundant_evs (SkolemInfoAnon
info, Bool
show_info))
(forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt)
[]
; MsgEnvelope TcRnMessage -> TcM ()
reportDiagnostic MsgEnvelope TcRnMessage
msg }
redundant_evs :: [TcId]
redundant_evs =
forall a. (a -> Bool) -> [a] -> [a]
filterOut TcId -> Bool
is_type_error forall a b. (a -> b) -> a -> b
$
case SkolemInfoAnon
info of
SkolemInfoAnon
InstSkol -> forall a. (a -> Bool) -> [a] -> [a]
filterOut (Type -> Bool
improving forall b c a. (b -> c) -> (a -> b) -> a -> c
. TcId -> Type
idType) [TcId]
ev_vars
SkolemInfoAnon
_ -> [TcId]
ev_vars
is_type_error :: TcId -> Bool
is_type_error = forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type -> Maybe Type
userTypeError_maybe forall b c a. (b -> c) -> (a -> b) -> a -> c
. TcId -> Type
idType
improving :: Type -> Bool
improving Type
pred
= forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Type -> Bool
isImprovementPred (Type
pred forall a. a -> [a] -> [a]
: Type -> [Type]
transSuperClasses Type
pred)
reportBadTelescope :: SolverReportErrCtxt -> TcLclEnv -> SkolemInfoAnon -> [TcTyVar] -> TcM ()
reportBadTelescope :: SolverReportErrCtxt
-> TcLclEnv -> SkolemInfoAnon -> [TcId] -> TcM ()
reportBadTelescope SolverReportErrCtxt
ctxt TcLclEnv
env (ForAllSkol TyVarBndrs
telescope) [TcId]
skols
= do { MsgEnvelope TcRnMessage
msg <- TcLclEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport
TcLclEnv
env
([SolverReportWithCtxt]
-> DiagnosticReason -> [GhcHint] -> TcRnMessage
TcRnSolverReport [SolverReportWithCtxt
report] DiagnosticReason
ErrorWithoutFlag [GhcHint]
noHints)
(forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt)
[]
; MsgEnvelope TcRnMessage -> TcM ()
reportDiagnostic MsgEnvelope TcRnMessage
msg }
where
report :: SolverReportWithCtxt
report = SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt forall a b. (a -> b) -> a -> b
$ TyVarBndrs -> [TcId] -> TcSolverReportMsg
BadTelescope TyVarBndrs
telescope [TcId]
skols
reportBadTelescope SolverReportErrCtxt
_ TcLclEnv
_ SkolemInfoAnon
skol_info [TcId]
skols
= forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"reportBadTelescope" (forall a. Outputable a => a -> SDoc
ppr SkolemInfoAnon
skol_info SDoc -> SDoc -> SDoc
$$ forall a. Outputable a => a -> SDoc
ppr [TcId]
skols)
ignoreConstraint :: Ct -> Bool
ignoreConstraint :: Ct -> Bool
ignoreConstraint Ct
ct
| CtOrigin
AssocFamPatOrigin <- Ct -> CtOrigin
ctOrigin Ct
ct
= Bool
True
| Bool
otherwise
= Bool
False
mkErrorItem :: Ct -> TcM (Maybe ErrorItem)
mkErrorItem :: Ct -> TcM (Maybe ErrorItem)
mkErrorItem Ct
ct
| Ct -> Bool
ignoreConstraint Ct
ct
= do { String -> SDoc -> TcM ()
traceTc String
"Ignoring constraint:" (forall a. Outputable a => a -> SDoc
ppr Ct
ct)
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing }
| Bool
otherwise
= do { let loc :: CtLoc
loc = Ct -> CtLoc
ctLoc Ct
ct
flav :: CtFlavour
flav = Ct -> CtFlavour
ctFlavour Ct
ct
; (Bool
suppress, Maybe TcEvDest
m_evdest) <- case Ct -> CtEvidence
ctEvidence Ct
ct of
CtGiven {} -> forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
False, forall a. Maybe a
Nothing)
CtWanted { ctev_rewriters :: CtEvidence -> RewriterSet
ctev_rewriters = RewriterSet
rewriters, ctev_dest :: CtEvidence -> TcEvDest
ctev_dest = TcEvDest
dest }
-> do { Bool
supp <- RewriterSet -> TcM Bool
anyUnfilledCoercionHoles RewriterSet
rewriters
; forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
supp, forall a. a -> Maybe a
Just TcEvDest
dest) }
; let m_reason :: Maybe CtIrredReason
m_reason = case Ct
ct of CIrredCan { cc_reason :: Ct -> CtIrredReason
cc_reason = CtIrredReason
reason } -> forall a. a -> Maybe a
Just CtIrredReason
reason
Ct
_ -> forall a. Maybe a
Nothing
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ EI { ei_pred :: Type
ei_pred = Ct -> Type
ctPred Ct
ct
, ei_evdest :: Maybe TcEvDest
ei_evdest = Maybe TcEvDest
m_evdest
, ei_flavour :: CtFlavour
ei_flavour = CtFlavour
flav
, ei_loc :: CtLoc
ei_loc = CtLoc
loc
, ei_m_reason :: Maybe CtIrredReason
ei_m_reason = Maybe CtIrredReason
m_reason
, ei_suppress :: Bool
ei_suppress = Bool
suppress }}
reportWanteds :: SolverReportErrCtxt -> TcLevel -> WantedConstraints -> TcM ()
reportWanteds :: SolverReportErrCtxt -> TcLevel -> WantedConstraints -> TcM ()
reportWanteds SolverReportErrCtxt
ctxt TcLevel
tc_lvl wc :: WantedConstraints
wc@(WC { wc_simple :: WantedConstraints -> Cts
wc_simple = Cts
simples, wc_impl :: WantedConstraints -> Bag Implication
wc_impl = Bag Implication
implics
, wc_errors :: WantedConstraints -> Bag DelayedError
wc_errors = Bag DelayedError
errs })
| WantedConstraints -> Bool
isEmptyWC WantedConstraints
wc = String -> SDoc -> TcM ()
traceTc String
"reportWanteds empty WC" SDoc
empty
| Bool
otherwise
= do { [ErrorItem]
tidy_items <- forall (m :: * -> *) a b.
Applicative m =>
(a -> m (Maybe b)) -> [a] -> m [b]
mapMaybeM Ct -> TcM (Maybe ErrorItem)
mkErrorItem [Ct]
tidy_cts
; String -> SDoc -> TcM ()
traceTc String
"reportWanteds 1" ([SDoc] -> SDoc
vcat [ String -> SDoc
text String
"Simples =" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Cts
simples
, String -> SDoc
text String
"Suppress =" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr (SolverReportErrCtxt -> Bool
cec_suppress SolverReportErrCtxt
ctxt)
, String -> SDoc
text String
"tidy_cts =" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [Ct]
tidy_cts
, String -> SDoc
text String
"tidy_items =" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
tidy_items
, String -> SDoc
text String
"tidy_errs =" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [DelayedError]
tidy_errs ])
; forall (m :: * -> *).
(HasCallStack, Monad m) =>
m Bool -> SDoc -> m ()
assertPprM
( do { Bool
errs_already <- forall r. TcRn r -> TcRn r -> TcRn r
ifErrsM (forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True) (forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False)
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
Bool
errs_already Bool -> Bool -> Bool
||
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Cts
simples Bool -> Bool -> Bool
||
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Ct -> Bool
ignoreConstraint Cts
simples Bool -> Bool -> Bool
||
Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ErrorItem -> Bool
ei_suppress [ErrorItem]
tidy_items)
} )
([SDoc] -> SDoc
vcat [String -> SDoc
text String
"reportWanteds is suppressing all errors"])
; let ([Hole]
out_of_scope, [Hole]
other_holes, [NotConcreteError]
not_conc_errs) = [DelayedError] -> ([Hole], [Hole], [NotConcreteError])
partition_errors [DelayedError]
tidy_errs
ctxt_for_scope_errs :: SolverReportErrCtxt
ctxt_for_scope_errs = SolverReportErrCtxt
ctxt { cec_suppress :: Bool
cec_suppress = Bool
False }
; (()
_, Bool
no_out_of_scope) <- forall a. TcRn a -> TcRn (a, Bool)
askNoErrs forall a b. (a -> b) -> a -> b
$
[ErrorItem] -> SolverReportErrCtxt -> [Hole] -> TcM ()
reportHoles [ErrorItem]
tidy_items SolverReportErrCtxt
ctxt_for_scope_errs [Hole]
out_of_scope
; let ctxt_for_insols :: SolverReportErrCtxt
ctxt_for_insols = SolverReportErrCtxt
ctxt { cec_suppress :: Bool
cec_suppress = Bool -> Bool
not Bool
no_out_of_scope }
; [ErrorItem] -> SolverReportErrCtxt -> [Hole] -> TcM ()
reportHoles [ErrorItem]
tidy_items SolverReportErrCtxt
ctxt_for_insols [Hole]
other_holes
; SolverReportErrCtxt -> [NotConcreteError] -> TcM ()
reportNotConcreteErrs SolverReportErrCtxt
ctxt_for_insols [NotConcreteError]
not_conc_errs
; let ([ErrorItem]
suppressed_items, [ErrorItem]
items0) = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition ErrorItem -> Bool
suppress [ErrorItem]
tidy_items
; String -> SDoc -> TcM ()
traceTc String
"reportWanteds suppressed:" (forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
suppressed_items)
; (SolverReportErrCtxt
ctxt1, [ErrorItem]
items1) <- SolverReportErrCtxt
-> [ReporterSpec]
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
tryReporters SolverReportErrCtxt
ctxt_for_insols [ReporterSpec]
report1 [ErrorItem]
items0
; let ctxt2 :: SolverReportErrCtxt
ctxt2 = SolverReportErrCtxt
ctxt1 { cec_suppress :: Bool
cec_suppress = SolverReportErrCtxt -> Bool
cec_suppress SolverReportErrCtxt
ctxt Bool -> Bool -> Bool
|| SolverReportErrCtxt -> Bool
cec_suppress SolverReportErrCtxt
ctxt1 }
; (SolverReportErrCtxt
ctxt3, [ErrorItem]
leftovers) <- SolverReportErrCtxt
-> [ReporterSpec]
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
tryReporters SolverReportErrCtxt
ctxt2 [ReporterSpec]
report2 [ErrorItem]
items1
; forall (m :: * -> *).
(HasCallStack, Applicative m) =>
Bool -> SDoc -> m ()
massertPpr (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ErrorItem]
leftovers)
(String -> SDoc
text String
"The following unsolved Wanted constraints \
\have not been reported to the user:"
SDoc -> SDoc -> SDoc
$$ forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
leftovers)
; forall (m :: * -> *) a b. Monad m => (a -> m b) -> Bag a -> m ()
mapBagM_ (SolverReportErrCtxt -> Implication -> TcM ()
reportImplic SolverReportErrCtxt
ctxt2) Bag Implication
implics
; TcM () -> TcM ()
whenNoErrs forall a b. (a -> b) -> a -> b
$
do { (SolverReportErrCtxt
_, [ErrorItem]
more_leftovers) <- SolverReportErrCtxt
-> [ReporterSpec]
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
tryReporters SolverReportErrCtxt
ctxt3 forall {p}. [(String, ErrorItem -> p -> Bool, Bool, Reporter)]
report3 [ErrorItem]
suppressed_items
; forall (m :: * -> *).
(HasCallStack, Applicative m) =>
Bool -> SDoc -> m ()
massertPpr (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ErrorItem]
more_leftovers) (forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
more_leftovers) } }
where
env :: TidyEnv
env = SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt
tidy_cts :: [Ct]
tidy_cts = forall a. Bag a -> [a]
bagToList (forall a b. (a -> b) -> Bag a -> Bag b
mapBag (TidyEnv -> Ct -> Ct
tidyCt TidyEnv
env) Cts
simples)
tidy_errs :: [DelayedError]
tidy_errs = forall a. Bag a -> [a]
bagToList (forall a b. (a -> b) -> Bag a -> Bag b
mapBag (TidyEnv -> DelayedError -> DelayedError
tidyDelayedError TidyEnv
env) Bag DelayedError
errs)
partition_errors :: [DelayedError] -> ([Hole], [Hole], [NotConcreteError])
partition_errors :: [DelayedError] -> ([Hole], [Hole], [NotConcreteError])
partition_errors = [Hole]
-> [Hole]
-> [NotConcreteError]
-> [DelayedError]
-> ([Hole], [Hole], [NotConcreteError])
go [] [] []
where
go :: [Hole]
-> [Hole]
-> [NotConcreteError]
-> [DelayedError]
-> ([Hole], [Hole], [NotConcreteError])
go [Hole]
out_of_scope [Hole]
other_holes [NotConcreteError]
syn_eqs []
= ([Hole]
out_of_scope, [Hole]
other_holes, [NotConcreteError]
syn_eqs)
go [Hole]
es1 [Hole]
es2 [NotConcreteError]
es3 (DelayedError
err:[DelayedError]
errs)
| ([Hole]
es1, [Hole]
es2, [NotConcreteError]
es3) <- [Hole]
-> [Hole]
-> [NotConcreteError]
-> [DelayedError]
-> ([Hole], [Hole], [NotConcreteError])
go [Hole]
es1 [Hole]
es2 [NotConcreteError]
es3 [DelayedError]
errs
= case DelayedError
err of
DE_Hole Hole
hole
| Hole -> Bool
isOutOfScopeHole Hole
hole
-> (Hole
hole forall a. a -> [a] -> [a]
: [Hole]
es1, [Hole]
es2, [NotConcreteError]
es3)
| Bool
otherwise
-> ([Hole]
es1, Hole
hole forall a. a -> [a] -> [a]
: [Hole]
es2, [NotConcreteError]
es3)
DE_NotConcrete NotConcreteError
err
-> ([Hole]
es1, [Hole]
es2, NotConcreteError
err forall a. a -> [a] -> [a]
: [NotConcreteError]
es3)
suppress :: ErrorItem -> Bool
suppress :: ErrorItem -> Bool
suppress ErrorItem
item
| CtFlavour
Wanted <- ErrorItem -> CtFlavour
ei_flavour ErrorItem
item
= ErrorItem -> Bool
is_ww_fundep_item ErrorItem
item
| Bool
otherwise
= Bool
False
report1 :: [ReporterSpec]
report1 = [ (String
"custom_error", forall {p}. ErrorItem -> p -> Bool
is_user_type_error, Bool
True, Reporter
mkUserTypeErrorReporter)
, ReporterSpec
given_eq_spec
, (String
"insoluble2", forall {p}. p -> Pred -> Bool
utterly_wrong, Bool
True, (SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkEqErr)
, (String
"skolem eq1", ErrorItem -> Pred -> Bool
very_wrong, Bool
True, Reporter
mkSkolReporter)
, (String
"FixedRuntimeRep", ErrorItem -> Pred -> Bool
is_FRR, Bool
True, (SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
mkGroupReporter HasDebugCallStack =>
SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkFRRErr)
, (String
"skolem eq2", ErrorItem -> Pred -> Bool
skolem_eq, Bool
True, Reporter
mkSkolReporter)
, (String
"non-tv eq", forall {p}. p -> Pred -> Bool
non_tv_eq, Bool
True, Reporter
mkSkolReporter)
, (String
"Homo eqs", forall {p}. p -> Pred -> Bool
is_homo_equality, Bool
True, (SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkEqErr)
, (String
"Other eqs", ErrorItem -> Pred -> Bool
is_equality, Bool
True, (SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkEqErr)
]
report2 :: [ReporterSpec]
report2 = [ (String
"Implicit params", ErrorItem -> Pred -> Bool
is_ip, Bool
False, (SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkIPErr)
, (String
"Irreds", ErrorItem -> Pred -> Bool
is_irred, Bool
False, (SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkIrredErr)
, (String
"Dicts", ErrorItem -> Pred -> Bool
is_dict, Bool
False, (SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
mkGroupReporter HasDebugCallStack =>
SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkDictErr) ]
report3 :: [(String, ErrorItem -> p -> Bool, Bool, Reporter)]
report3 = [ (String
"wanted/wanted fundeps", forall {p}. ErrorItem -> p -> Bool
is_ww_fundep, Bool
True, (SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkEqErr)
]
is_dict, is_equality, is_ip, is_FRR, is_irred :: ErrorItem -> Pred -> Bool
is_given_eq :: ErrorItem -> Pred -> Bool
is_given_eq ErrorItem
item Pred
pred
| CtFlavour
Given <- ErrorItem -> CtFlavour
ei_flavour ErrorItem
item
, EqPred {} <- Pred
pred = Bool
True
| Bool
otherwise = Bool
False
utterly_wrong :: p -> Pred -> Bool
utterly_wrong p
_ (EqPred EqRel
NomEq Type
ty1 Type
ty2) = Type -> Bool
isRigidTy Type
ty1 Bool -> Bool -> Bool
&& Type -> Bool
isRigidTy Type
ty2
utterly_wrong p
_ Pred
_ = Bool
False
very_wrong :: ErrorItem -> Pred -> Bool
very_wrong ErrorItem
_ (EqPred EqRel
NomEq Type
ty1 Type
ty2) = TcLevel -> Type -> Bool
isSkolemTy TcLevel
tc_lvl Type
ty1 Bool -> Bool -> Bool
&& Type -> Bool
isRigidTy Type
ty2
very_wrong ErrorItem
_ Pred
_ = Bool
False
is_FRR :: ErrorItem -> Pred -> Bool
is_FRR ErrorItem
item Pred
_ = forall a. Maybe a -> Bool
isJust forall a b. (a -> b) -> a -> b
$ HasDebugCallStack => ErrorItem -> Maybe FixedRuntimeRepErrorInfo
fixedRuntimeRepOrigin_maybe ErrorItem
item
skolem_eq :: ErrorItem -> Pred -> Bool
skolem_eq ErrorItem
_ (EqPred EqRel
NomEq Type
ty1 Type
_) = TcLevel -> Type -> Bool
isSkolemTy TcLevel
tc_lvl Type
ty1
skolem_eq ErrorItem
_ Pred
_ = Bool
False
non_tv_eq :: p -> Pred -> Bool
non_tv_eq p
_ (EqPred EqRel
NomEq Type
ty1 Type
_) = Bool -> Bool
not (Type -> Bool
isTyVarTy Type
ty1)
non_tv_eq p
_ Pred
_ = Bool
False
is_user_type_error :: ErrorItem -> p -> Bool
is_user_type_error ErrorItem
item p
_ = Type -> Bool
isUserTypeError (ErrorItem -> Type
errorItemPred ErrorItem
item)
is_homo_equality :: p -> Pred -> Bool
is_homo_equality p
_ (EqPred EqRel
_ Type
ty1 Type
ty2)
= HasDebugCallStack => Type -> Type
tcTypeKind Type
ty1 HasDebugCallStack => Type -> Type -> Bool
`tcEqType` HasDebugCallStack => Type -> Type
tcTypeKind Type
ty2
is_homo_equality p
_ Pred
_
= Bool
False
is_equality :: ErrorItem -> Pred -> Bool
is_equality ErrorItem
_(EqPred {}) = Bool
True
is_equality ErrorItem
_ Pred
_ = Bool
False
is_dict :: ErrorItem -> Pred -> Bool
is_dict ErrorItem
_ (ClassPred {}) = Bool
True
is_dict ErrorItem
_ Pred
_ = Bool
False
is_ip :: ErrorItem -> Pred -> Bool
is_ip ErrorItem
_ (ClassPred Class
cls [Type]
_) = Class -> Bool
isIPClass Class
cls
is_ip ErrorItem
_ Pred
_ = Bool
False
is_irred :: ErrorItem -> Pred -> Bool
is_irred ErrorItem
_ (IrredPred {}) = Bool
True
is_irred ErrorItem
_ Pred
_ = Bool
False
is_ww_fundep :: ErrorItem -> p -> Bool
is_ww_fundep ErrorItem
item p
_ = ErrorItem -> Bool
is_ww_fundep_item ErrorItem
item
is_ww_fundep_item :: ErrorItem -> Bool
is_ww_fundep_item = CtOrigin -> Bool
isWantedWantedFunDepOrigin forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorItem -> CtOrigin
errorItemOrigin
given_eq_spec :: ReporterSpec
given_eq_spec
| Bool
has_gadt_match_here
= (String
"insoluble1a", ErrorItem -> Pred -> Bool
is_given_eq, Bool
True, Reporter
mkGivenErrorReporter)
| Bool
otherwise
= (String
"insoluble1b", ErrorItem -> Pred -> Bool
is_given_eq, Bool
False, Reporter
ignoreErrorReporter)
has_gadt_match_here :: Bool
has_gadt_match_here = [Implication] -> Bool
has_gadt_match (SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt)
has_gadt_match :: [Implication] -> Bool
has_gadt_match [] = Bool
False
has_gadt_match (Implication
implic : [Implication]
implics)
| PatSkol {} <- Implication -> SkolemInfoAnon
ic_info Implication
implic
, Implication -> HasGivenEqs
ic_given_eqs Implication
implic forall a. Eq a => a -> a -> Bool
/= HasGivenEqs
NoGivenEqs
, Implication -> Bool
ic_warn_inaccessible Implication
implic
= Bool
True
| Bool
otherwise
= [Implication] -> Bool
has_gadt_match [Implication]
implics
isSkolemTy :: TcLevel -> Type -> Bool
isSkolemTy :: TcLevel -> Type -> Bool
isSkolemTy TcLevel
tc_lvl Type
ty
| Just TcId
tv <- Type -> Maybe TcId
getTyVar_maybe Type
ty
= TcId -> Bool
isSkolemTyVar TcId
tv
Bool -> Bool -> Bool
|| (TcId -> Bool
isTyVarTyVar TcId
tv Bool -> Bool -> Bool
&& TcLevel -> TcId -> Bool
isTouchableMetaTyVar TcLevel
tc_lvl TcId
tv)
| Bool
otherwise
= Bool
False
isTyFun_maybe :: Type -> Maybe TyCon
isTyFun_maybe :: Type -> Maybe TyCon
isTyFun_maybe Type
ty = case HasCallStack => Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
ty of
Just (TyCon
tc,[Type]
_) | TyCon -> Bool
isTypeFamilyTyCon TyCon
tc -> forall a. a -> Maybe a
Just TyCon
tc
Maybe (TyCon, [Type])
_ -> forall a. Maybe a
Nothing
type Reporter
= SolverReportErrCtxt -> [ErrorItem] -> TcM ()
type ReporterSpec
= ( String
, ErrorItem -> Pred -> Bool
, Bool
, Reporter)
mkSkolReporter :: Reporter
mkSkolReporter :: Reporter
mkSkolReporter SolverReportErrCtxt
ctxt [ErrorItem]
items
= forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
reportGroup SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkEqErr SolverReportErrCtxt
ctxt) ([ErrorItem] -> [[ErrorItem]]
group [ErrorItem]
items)
where
group :: [ErrorItem] -> [[ErrorItem]]
group [] = []
group (ErrorItem
item:[ErrorItem]
items) = (ErrorItem
item forall a. a -> [a] -> [a]
: [ErrorItem]
yeses) forall a. a -> [a] -> [a]
: [ErrorItem] -> [[ErrorItem]]
group [ErrorItem]
noes
where
([ErrorItem]
yeses, [ErrorItem]
noes) = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (ErrorItem -> ErrorItem -> Bool
group_with ErrorItem
item) [ErrorItem]
items
group_with :: ErrorItem -> ErrorItem -> Bool
group_with ErrorItem
item1 ErrorItem
item2
| Ordering
EQ <- ErrorItem -> ErrorItem -> Ordering
cmp_loc ErrorItem
item1 ErrorItem
item2 = Bool
True
| ErrorItem -> ErrorItem -> Bool
eq_lhs_type ErrorItem
item1 ErrorItem
item2 = Bool
True
| Bool
otherwise = Bool
False
reportHoles :: [ErrorItem]
-> SolverReportErrCtxt -> [Hole] -> TcM ()
reportHoles :: [ErrorItem] -> SolverReportErrCtxt -> [Hole] -> TcM ()
reportHoles [ErrorItem]
tidy_items SolverReportErrCtxt
ctxt [Hole]
holes
= do
DiagOpts
diag_opts <- DynFlags -> DiagOpts
initDiagOpts forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
let severity :: Severity
severity = DiagOpts -> DiagnosticReason -> Severity
diagReasonSeverity DiagOpts
diag_opts (SolverReportErrCtxt -> DiagnosticReason
cec_type_holes SolverReportErrCtxt
ctxt)
holes' :: [Hole]
holes' = forall a. (a -> Bool) -> [a] -> [a]
filter (Severity -> Hole -> Bool
keepThisHole Severity
severity) [Hole]
holes
(TidyEnv
tidy_env', NameEnv Type
lcl_name_cache) <- TidyEnv -> [TcLclEnv] -> TcM (TidyEnv, NameEnv Type)
zonkTidyTcLclEnvs (SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt) (forall a b. (a -> b) -> [a] -> [b]
map (CtLoc -> TcLclEnv
ctl_env forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hole -> CtLoc
hole_loc) [Hole]
holes')
let ctxt' :: SolverReportErrCtxt
ctxt' = SolverReportErrCtxt
ctxt { cec_tidy :: TidyEnv
cec_tidy = TidyEnv
tidy_env' }
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Hole]
holes' forall a b. (a -> b) -> a -> b
$ \Hole
hole -> do { MsgEnvelope TcRnMessage
msg <- NameEnv Type
-> [ErrorItem]
-> SolverReportErrCtxt
-> Hole
-> TcM (MsgEnvelope TcRnMessage)
mkHoleError NameEnv Type
lcl_name_cache [ErrorItem]
tidy_items SolverReportErrCtxt
ctxt' Hole
hole
; MsgEnvelope TcRnMessage -> TcM ()
reportDiagnostic MsgEnvelope TcRnMessage
msg }
keepThisHole :: Severity -> Hole -> Bool
keepThisHole :: Severity -> Hole -> Bool
keepThisHole Severity
sev Hole
hole
= case Hole -> HoleSort
hole_sort Hole
hole of
ExprHole {} -> Bool
True
HoleSort
TypeHole -> Bool
keep_type_hole
HoleSort
ConstraintHole -> Bool
keep_type_hole
where
keep_type_hole :: Bool
keep_type_hole = case Severity
sev of
Severity
SevIgnore -> Bool
False
Severity
_ -> Bool
True
zonkTidyTcLclEnvs :: TidyEnv -> [TcLclEnv] -> TcM (TidyEnv, NameEnv Type)
zonkTidyTcLclEnvs :: TidyEnv -> [TcLclEnv] -> TcM (TidyEnv, NameEnv Type)
zonkTidyTcLclEnvs TidyEnv
tidy_env [TcLclEnv]
lcls = forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (TidyEnv, NameEnv Type) -> TcBinder -> TcM (TidyEnv, NameEnv Type)
go (TidyEnv
tidy_env, forall a. NameEnv a
emptyNameEnv) (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TcLclEnv -> TcBinderStack
tcl_bndrs [TcLclEnv]
lcls)
where
go :: (TidyEnv, NameEnv Type) -> TcBinder -> TcM (TidyEnv, NameEnv Type)
go (TidyEnv, NameEnv Type)
envs TcBinder
tc_bndr = case TcBinder
tc_bndr of
TcTvBndr {} -> forall (m :: * -> *) a. Monad m => a -> m a
return (TidyEnv, NameEnv Type)
envs
TcIdBndr TcId
id TopLevelFlag
_top_lvl -> Name
-> Type -> (TidyEnv, NameEnv Type) -> TcM (TidyEnv, NameEnv Type)
go_one (TcId -> Name
idName TcId
id) (TcId -> Type
idType TcId
id) (TidyEnv, NameEnv Type)
envs
TcIdBndr_ExpType Name
name ExpType
et TopLevelFlag
_top_lvl ->
do { Maybe Type
mb_ty <- ExpType -> TcM (Maybe Type)
readExpType_maybe ExpType
et
; case Maybe Type
mb_ty of
Just Type
ty -> Name
-> Type -> (TidyEnv, NameEnv Type) -> TcM (TidyEnv, NameEnv Type)
go_one Name
name Type
ty (TidyEnv, NameEnv Type)
envs
Maybe Type
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return (TidyEnv, NameEnv Type)
envs
}
go_one :: Name
-> Type -> (TidyEnv, NameEnv Type) -> TcM (TidyEnv, NameEnv Type)
go_one Name
name Type
ty (TidyEnv
tidy_env, NameEnv Type
name_env) = do
if Name
name forall a. Name -> NameEnv a -> Bool
`elemNameEnv` NameEnv Type
name_env
then forall (m :: * -> *) a. Monad m => a -> m a
return (TidyEnv
tidy_env, NameEnv Type
name_env)
else do
(TidyEnv
tidy_env', Type
tidy_ty) <- TidyEnv -> Type -> TcM (TidyEnv, Type)
zonkTidyTcType TidyEnv
tidy_env Type
ty
forall (m :: * -> *) a. Monad m => a -> m a
return (TidyEnv
tidy_env', forall a. NameEnv a -> Name -> a -> NameEnv a
extendNameEnv NameEnv Type
name_env Name
name Type
tidy_ty)
reportNotConcreteErrs :: SolverReportErrCtxt -> [NotConcreteError] -> TcM ()
reportNotConcreteErrs :: SolverReportErrCtxt -> [NotConcreteError] -> TcM ()
reportNotConcreteErrs SolverReportErrCtxt
_ [] = forall (m :: * -> *) a. Monad m => a -> m a
return ()
reportNotConcreteErrs SolverReportErrCtxt
ctxt errs :: [NotConcreteError]
errs@(NotConcreteError
err0:[NotConcreteError]
_)
= do { MsgEnvelope TcRnMessage
msg <- TcLclEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport (CtLoc -> TcLclEnv
ctLocEnv (NotConcreteError -> CtLoc
nce_loc NotConcreteError
err0)) TcRnMessage
diag (forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt) []
; MsgEnvelope TcRnMessage -> TcM ()
reportDiagnostic MsgEnvelope TcRnMessage
msg }
where
frr_origins :: [FixedRuntimeRepErrorInfo]
frr_origins = [NotConcreteError] -> [FixedRuntimeRepErrorInfo]
acc_errors [NotConcreteError]
errs
diag :: TcRnMessage
diag = [SolverReportWithCtxt]
-> DiagnosticReason -> [GhcHint] -> TcRnMessage
TcRnSolverReport
[SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt ([FixedRuntimeRepErrorInfo] -> TcSolverReportMsg
FixedRuntimeRepError [FixedRuntimeRepErrorInfo]
frr_origins)]
DiagnosticReason
ErrorWithoutFlag [GhcHint]
noHints
acc_errors :: [NotConcreteError] -> [FixedRuntimeRepErrorInfo]
acc_errors = [FixedRuntimeRepErrorInfo]
-> [NotConcreteError] -> [FixedRuntimeRepErrorInfo]
go []
where
go :: [FixedRuntimeRepErrorInfo]
-> [NotConcreteError] -> [FixedRuntimeRepErrorInfo]
go [FixedRuntimeRepErrorInfo]
frr_errs [] = [FixedRuntimeRepErrorInfo]
frr_errs
go [FixedRuntimeRepErrorInfo]
frr_errs (NotConcreteError
err:[NotConcreteError]
errs)
| [FixedRuntimeRepErrorInfo]
frr_errs <- [FixedRuntimeRepErrorInfo]
-> [NotConcreteError] -> [FixedRuntimeRepErrorInfo]
go [FixedRuntimeRepErrorInfo]
frr_errs [NotConcreteError]
errs
= case NotConcreteError
err of
NCE_FRR
{ nce_frr_origin :: NotConcreteError -> FixedRuntimeRepOrigin
nce_frr_origin = FixedRuntimeRepOrigin
frr_orig
, nce_reasons :: NotConcreteError -> NonEmpty NotConcreteReason
nce_reasons = NonEmpty NotConcreteReason
_not_conc } ->
FRR_Info
{ frr_info_origin :: FixedRuntimeRepOrigin
frr_info_origin = FixedRuntimeRepOrigin
frr_orig
, frr_info_not_concrete :: Maybe (TcId, Type)
frr_info_not_concrete = forall a. Maybe a
Nothing }
forall a. a -> [a] -> [a]
: [FixedRuntimeRepErrorInfo]
frr_errs
mkUserTypeErrorReporter :: Reporter
mkUserTypeErrorReporter :: Reporter
mkUserTypeErrorReporter SolverReportErrCtxt
ctxt
= forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ forall a b. (a -> b) -> a -> b
$ \ErrorItem
item -> do { let err :: SolverReport
err = SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt forall a b. (a -> b) -> a -> b
$ ErrorItem -> TcSolverReportMsg
mkUserTypeError ErrorItem
item
; SolverReportErrCtxt -> [ErrorItem] -> SolverReport -> TcM ()
maybeReportError SolverReportErrCtxt
ctxt [ErrorItem
item] SolverReport
err
; SolverReportErrCtxt -> SolverReport -> ErrorItem -> TcM ()
addDeferredBinding SolverReportErrCtxt
ctxt SolverReport
err ErrorItem
item }
mkUserTypeError :: ErrorItem -> TcSolverReportMsg
mkUserTypeError :: ErrorItem -> TcSolverReportMsg
mkUserTypeError ErrorItem
item =
case Type -> Maybe Type
getUserTypeErrorMsg (ErrorItem -> Type
errorItemPred ErrorItem
item) of
Just Type
msg -> Type -> TcSolverReportMsg
UserTypeError Type
msg
Maybe Type
Nothing -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"mkUserTypeError" (forall a. Outputable a => a -> SDoc
ppr ErrorItem
item)
mkGivenErrorReporter :: Reporter
mkGivenErrorReporter :: Reporter
mkGivenErrorReporter SolverReportErrCtxt
ctxt [ErrorItem]
items
= do { (SolverReportErrCtxt
ctxt, RelevantBindings
relevant_binds, ErrorItem
item) <- Bool
-> SolverReportErrCtxt
-> ErrorItem
-> TcM (SolverReportErrCtxt, RelevantBindings, ErrorItem)
relevantBindings Bool
True SolverReportErrCtxt
ctxt ErrorItem
item
; let (Implication
implic:[Implication]
_) = SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt
loc' :: CtLoc
loc' = CtLoc -> TcLclEnv -> CtLoc
setCtLocEnv (ErrorItem -> CtLoc
ei_loc ErrorItem
item) (Implication -> TcLclEnv
ic_env Implication
implic)
item' :: ErrorItem
item' = ErrorItem
item { ei_loc :: CtLoc
ei_loc = CtLoc
loc' }
; (AccReportMsgs
eq_err_msgs, [GhcHint]
_hints) <- SolverReportErrCtxt
-> ErrorItem -> Type -> Type -> TcM (AccReportMsgs, [GhcHint])
mkEqErr_help SolverReportErrCtxt
ctxt ErrorItem
item' Type
ty1 Type
ty2
; let supplementary :: [SolverReportSupplementary]
supplementary = [ RelevantBindings -> SolverReportSupplementary
SupplementaryBindings RelevantBindings
relevant_binds ]
msg :: TcRnMessage
msg = Implication -> NonEmpty SolverReportWithCtxt -> TcRnMessage
TcRnInaccessibleCode Implication
implic (forall a. NonEmpty a -> NonEmpty a
NE.reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map (SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt) forall a b. (a -> b) -> a -> b
$ AccReportMsgs
eq_err_msgs)
; MsgEnvelope TcRnMessage
msg <- TcLclEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport (CtLoc -> TcLclEnv
ctLocEnv CtLoc
loc') TcRnMessage
msg (forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt) [SolverReportSupplementary]
supplementary
; MsgEnvelope TcRnMessage -> TcM ()
reportDiagnostic MsgEnvelope TcRnMessage
msg }
where
(ErrorItem
item : [ErrorItem]
_ ) = [ErrorItem]
items
(Type
ty1, Type
ty2) = Type -> (Type, Type)
getEqPredTys (ErrorItem -> Type
errorItemPred ErrorItem
item)
ignoreErrorReporter :: Reporter
ignoreErrorReporter :: Reporter
ignoreErrorReporter SolverReportErrCtxt
ctxt [ErrorItem]
items
= do { String -> SDoc -> TcM ()
traceTc String
"mkGivenErrorReporter no" (forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
items SDoc -> SDoc -> SDoc
$$ forall a. Outputable a => a -> SDoc
ppr (SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt))
; forall (m :: * -> *) a. Monad m => a -> m a
return () }
mkGroupReporter :: (SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
mkGroupReporter :: (SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mk_err SolverReportErrCtxt
ctxt [ErrorItem]
items
= forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
reportGroup SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mk_err SolverReportErrCtxt
ctxt forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) (forall a. (a -> a -> Ordering) -> [a] -> [NonEmpty a]
equivClasses ErrorItem -> ErrorItem -> Ordering
cmp_loc [ErrorItem]
items)
eq_lhs_type :: ErrorItem -> ErrorItem -> Bool
eq_lhs_type :: ErrorItem -> ErrorItem -> Bool
eq_lhs_type ErrorItem
item1 ErrorItem
item2
= case (Type -> Pred
classifyPredType (ErrorItem -> Type
errorItemPred ErrorItem
item1), Type -> Pred
classifyPredType (ErrorItem -> Type
errorItemPred ErrorItem
item2)) of
(EqPred EqRel
eq_rel1 Type
ty1 Type
_, EqPred EqRel
eq_rel2 Type
ty2 Type
_) ->
(EqRel
eq_rel1 forall a. Eq a => a -> a -> Bool
== EqRel
eq_rel2) Bool -> Bool -> Bool
&& (Type
ty1 Type -> Type -> Bool
`eqType` Type
ty2)
(Pred, Pred)
_ -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"mkSkolReporter" (forall a. Outputable a => a -> SDoc
ppr ErrorItem
item1 SDoc -> SDoc -> SDoc
$$ forall a. Outputable a => a -> SDoc
ppr ErrorItem
item2)
cmp_loc :: ErrorItem -> ErrorItem -> Ordering
cmp_loc :: ErrorItem -> ErrorItem -> Ordering
cmp_loc ErrorItem
item1 ErrorItem
item2 = ErrorItem -> RealSrcLoc
get ErrorItem
item1 forall a. Ord a => a -> a -> Ordering
`compare` ErrorItem -> RealSrcLoc
get ErrorItem
item2
where
get :: ErrorItem -> RealSrcLoc
get ErrorItem
ei = RealSrcSpan -> RealSrcLoc
realSrcSpanStart (CtLoc -> RealSrcSpan
ctLocSpan (ErrorItem -> CtLoc
errorItemCtLoc ErrorItem
ei))
reportGroup :: (SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport) -> Reporter
reportGroup :: (SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport)
-> Reporter
reportGroup SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mk_err SolverReportErrCtxt
ctxt [ErrorItem]
items
= do { SolverReport
err <- SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mk_err SolverReportErrCtxt
ctxt [ErrorItem]
items
; String -> SDoc -> TcM ()
traceTc String
"About to maybeReportErr" forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat [ String -> SDoc
text String
"Constraint:" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
items
, String -> SDoc
text String
"cec_suppress =" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr (SolverReportErrCtxt -> Bool
cec_suppress SolverReportErrCtxt
ctxt)
, String -> SDoc
text String
"cec_defer_type_errors =" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr (SolverReportErrCtxt -> DiagnosticReason
cec_defer_type_errors SolverReportErrCtxt
ctxt) ]
; SolverReportErrCtxt -> [ErrorItem] -> SolverReport -> TcM ()
maybeReportError SolverReportErrCtxt
ctxt [ErrorItem]
items SolverReport
err
; String -> SDoc -> TcM ()
traceTc String
"reportGroup" (forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
items)
; forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (SolverReportErrCtxt -> SolverReport -> ErrorItem -> TcM ()
addDeferredBinding SolverReportErrCtxt
ctxt SolverReport
err) [ErrorItem]
items }
nonDeferrableOrigin :: CtOrigin -> Bool
nonDeferrableOrigin :: CtOrigin -> Bool
nonDeferrableOrigin CtOrigin
NonLinearPatternOrigin = Bool
True
nonDeferrableOrigin (UsageEnvironmentOf {}) = Bool
True
nonDeferrableOrigin (FRROrigin {}) = Bool
True
nonDeferrableOrigin CtOrigin
_ = Bool
False
maybeReportError :: SolverReportErrCtxt
-> [ErrorItem]
-> SolverReport -> TcM ()
maybeReportError :: SolverReportErrCtxt -> [ErrorItem] -> SolverReport -> TcM ()
maybeReportError SolverReportErrCtxt
ctxt items :: [ErrorItem]
items@(ErrorItem
item1:[ErrorItem]
_) (SolverReport { sr_important_msgs :: SolverReport -> [SolverReportWithCtxt]
sr_important_msgs = [SolverReportWithCtxt]
important
, sr_supplementary :: SolverReport -> [SolverReportSupplementary]
sr_supplementary = [SolverReportSupplementary]
supp
, sr_hints :: SolverReport -> [GhcHint]
sr_hints = [GhcHint]
hints })
= forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (SolverReportErrCtxt -> Bool
cec_suppress SolverReportErrCtxt
ctxt
Bool -> Bool -> Bool
|| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ErrorItem -> Bool
ei_suppress [ErrorItem]
items) forall a b. (a -> b) -> a -> b
$
do let reason :: DiagnosticReason
reason | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (CtOrigin -> Bool
nonDeferrableOrigin forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorItem -> CtOrigin
errorItemOrigin) [ErrorItem]
items = DiagnosticReason
ErrorWithoutFlag
| Bool
otherwise = SolverReportErrCtxt -> DiagnosticReason
cec_defer_type_errors SolverReportErrCtxt
ctxt
diag :: TcRnMessage
diag = [SolverReportWithCtxt]
-> DiagnosticReason -> [GhcHint] -> TcRnMessage
TcRnSolverReport [SolverReportWithCtxt]
important DiagnosticReason
reason [GhcHint]
hints
MsgEnvelope TcRnMessage
msg <- TcLclEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport (CtLoc -> TcLclEnv
ctLocEnv (ErrorItem -> CtLoc
errorItemCtLoc ErrorItem
item1)) TcRnMessage
diag (forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt) [SolverReportSupplementary]
supp
MsgEnvelope TcRnMessage -> TcM ()
reportDiagnostic MsgEnvelope TcRnMessage
msg
maybeReportError SolverReportErrCtxt
_ [ErrorItem]
_ SolverReport
_ = forall a. String -> a
panic String
"maybeReportError"
addDeferredBinding :: SolverReportErrCtxt -> SolverReport -> ErrorItem -> TcM ()
addDeferredBinding :: SolverReportErrCtxt -> SolverReport -> ErrorItem -> TcM ()
addDeferredBinding SolverReportErrCtxt
ctxt SolverReport
err (EI { ei_evdest :: ErrorItem -> Maybe TcEvDest
ei_evdest = Just TcEvDest
dest, ei_pred :: ErrorItem -> Type
ei_pred = Type
item_ty
, ei_loc :: ErrorItem -> CtLoc
ei_loc = CtLoc
loc })
| SolverReportErrCtxt -> Bool
deferringAnyBindings SolverReportErrCtxt
ctxt
= do { EvTerm
err_tm <- SolverReportErrCtxt -> CtLoc -> Type -> SolverReport -> TcM EvTerm
mkErrorTerm SolverReportErrCtxt
ctxt CtLoc
loc Type
item_ty SolverReport
err
; let ev_binds_var :: EvBindsVar
ev_binds_var = SolverReportErrCtxt -> EvBindsVar
cec_binds SolverReportErrCtxt
ctxt
; case TcEvDest
dest of
EvVarDest TcId
evar
-> EvBindsVar -> EvBind -> TcM ()
addTcEvBind EvBindsVar
ev_binds_var forall a b. (a -> b) -> a -> b
$ TcId -> EvTerm -> EvBind
mkWantedEvBind TcId
evar EvTerm
err_tm
HoleDest CoercionHole
hole
-> do {
let co_var :: TcId
co_var = CoercionHole -> TcId
coHoleCoVar CoercionHole
hole
; EvBindsVar -> EvBind -> TcM ()
addTcEvBind EvBindsVar
ev_binds_var forall a b. (a -> b) -> a -> b
$ TcId -> EvTerm -> EvBind
mkWantedEvBind TcId
co_var EvTerm
err_tm
; CoercionHole -> TcCoercionN -> TcM ()
fillCoercionHole CoercionHole
hole (TcId -> TcCoercionN
mkTcCoVarCo TcId
co_var) } }
addDeferredBinding SolverReportErrCtxt
_ SolverReport
_ ErrorItem
_ = forall (m :: * -> *) a. Monad m => a -> m a
return ()
mkErrorTerm :: SolverReportErrCtxt -> CtLoc -> Type
-> SolverReport -> TcM EvTerm
mkErrorTerm :: SolverReportErrCtxt -> CtLoc -> Type -> SolverReport -> TcM EvTerm
mkErrorTerm SolverReportErrCtxt
ctxt CtLoc
ct_loc Type
ty (SolverReport { sr_important_msgs :: SolverReport -> [SolverReportWithCtxt]
sr_important_msgs = [SolverReportWithCtxt]
important, sr_supplementary :: SolverReport -> [SolverReportSupplementary]
sr_supplementary = [SolverReportSupplementary]
supp })
= do { MsgEnvelope TcRnMessage
msg <- TcLclEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport
(CtLoc -> TcLclEnv
ctLocEnv CtLoc
ct_loc)
([SolverReportWithCtxt]
-> DiagnosticReason -> [GhcHint] -> TcRnMessage
TcRnSolverReport [SolverReportWithCtxt]
important DiagnosticReason
ErrorWithoutFlag [GhcHint]
noHints) (forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt) [SolverReportSupplementary]
supp
; DynFlags
dflags <- forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
; let err_msg :: SDoc
err_msg = forall e. Diagnostic e => MsgEnvelope e -> SDoc
pprLocMsgEnvelope MsgEnvelope TcRnMessage
msg
err_str :: String
err_str = DynFlags -> SDoc -> String
showSDoc DynFlags
dflags forall a b. (a -> b) -> a -> b
$
SDoc
err_msg SDoc -> SDoc -> SDoc
$$ String -> SDoc
text String
"(deferred type error)"
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Type -> String -> EvTerm
evDelayedError Type
ty String
err_str }
tryReporters :: SolverReportErrCtxt -> [ReporterSpec] -> [ErrorItem] -> TcM (SolverReportErrCtxt, [ErrorItem])
tryReporters :: SolverReportErrCtxt
-> [ReporterSpec]
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
tryReporters SolverReportErrCtxt
ctxt [ReporterSpec]
reporters [ErrorItem]
items
= do { let ([ErrorItem]
vis_items, [ErrorItem]
invis_items)
= forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (CtOrigin -> Bool
isVisibleOrigin forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorItem -> CtOrigin
errorItemOrigin) [ErrorItem]
items
; String -> SDoc -> TcM ()
traceTc String
"tryReporters {" (forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
vis_items SDoc -> SDoc -> SDoc
$$ forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
invis_items)
; (SolverReportErrCtxt
ctxt', [ErrorItem]
items') <- SolverReportErrCtxt
-> [ReporterSpec]
-> [ErrorItem]
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
go SolverReportErrCtxt
ctxt [ReporterSpec]
reporters [ErrorItem]
vis_items [ErrorItem]
invis_items
; String -> SDoc -> TcM ()
traceTc String
"tryReporters }" (forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
items')
; forall (m :: * -> *) a. Monad m => a -> m a
return (SolverReportErrCtxt
ctxt', [ErrorItem]
items') }
where
go :: SolverReportErrCtxt
-> [ReporterSpec]
-> [ErrorItem]
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
go SolverReportErrCtxt
ctxt [] [ErrorItem]
vis_items [ErrorItem]
invis_items
= forall (m :: * -> *) a. Monad m => a -> m a
return (SolverReportErrCtxt
ctxt, [ErrorItem]
vis_items forall a. [a] -> [a] -> [a]
++ [ErrorItem]
invis_items)
go SolverReportErrCtxt
ctxt (ReporterSpec
r : [ReporterSpec]
rs) [ErrorItem]
vis_items [ErrorItem]
invis_items
= do { (SolverReportErrCtxt
ctxt', [ErrorItem]
vis_items') <- SolverReportErrCtxt
-> ReporterSpec
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
tryReporter SolverReportErrCtxt
ctxt ReporterSpec
r [ErrorItem]
vis_items
; (SolverReportErrCtxt
ctxt'', [ErrorItem]
invis_items') <- SolverReportErrCtxt
-> ReporterSpec
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
tryReporter SolverReportErrCtxt
ctxt' ReporterSpec
r [ErrorItem]
invis_items
; SolverReportErrCtxt
-> [ReporterSpec]
-> [ErrorItem]
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
go SolverReportErrCtxt
ctxt'' [ReporterSpec]
rs [ErrorItem]
vis_items' [ErrorItem]
invis_items' }
tryReporter :: SolverReportErrCtxt -> ReporterSpec -> [ErrorItem] -> TcM (SolverReportErrCtxt, [ErrorItem])
tryReporter :: SolverReportErrCtxt
-> ReporterSpec
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
tryReporter SolverReportErrCtxt
ctxt (String
str, ErrorItem -> Pred -> Bool
keep_me, Bool
suppress_after, Reporter
reporter) [ErrorItem]
items
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ErrorItem]
yeses
= forall (m :: * -> *) a. Monad m => a -> m a
return (SolverReportErrCtxt
ctxt, [ErrorItem]
items)
| Bool
otherwise
= do { String -> SDoc -> TcM ()
traceTc String
"tryReporter{ " (String -> SDoc
text String
str SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
yeses)
; (()
_, Bool
no_errs) <- forall a. TcRn a -> TcRn (a, Bool)
askNoErrs (Reporter
reporter SolverReportErrCtxt
ctxt [ErrorItem]
yeses)
; let suppress_now :: Bool
suppress_now = Bool -> Bool
not Bool
no_errs Bool -> Bool -> Bool
&& Bool
suppress_after
ctxt' :: SolverReportErrCtxt
ctxt' = SolverReportErrCtxt
ctxt { cec_suppress :: Bool
cec_suppress = Bool
suppress_now Bool -> Bool -> Bool
|| SolverReportErrCtxt -> Bool
cec_suppress SolverReportErrCtxt
ctxt }
; String -> SDoc -> TcM ()
traceTc String
"tryReporter end }" (String -> SDoc
text String
str SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr (SolverReportErrCtxt -> Bool
cec_suppress SolverReportErrCtxt
ctxt) SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Bool
suppress_after)
; forall (m :: * -> *) a. Monad m => a -> m a
return (SolverReportErrCtxt
ctxt', [ErrorItem]
nos) }
where
([ErrorItem]
yeses, [ErrorItem]
nos) = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition ErrorItem -> Bool
keep [ErrorItem]
items
keep :: ErrorItem -> Bool
keep ErrorItem
item = ErrorItem -> Pred -> Bool
keep_me ErrorItem
item (Type -> Pred
classifyPredType (ErrorItem -> Type
errorItemPred ErrorItem
item))
mkErrorReport :: TcLclEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport :: TcLclEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport TcLclEnv
tcl_env TcRnMessage
msg Maybe SolverReportErrCtxt
mb_ctxt [SolverReportSupplementary]
supplementary
= do { Maybe SDoc
mb_context <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\ SolverReportErrCtxt
ctxt -> TidyEnv -> [ErrCtxt] -> IOEnv (Env TcGblEnv TcLclEnv) SDoc
mkErrInfo (SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt) (TcLclEnv -> [ErrCtxt]
tcl_ctxt TcLclEnv
tcl_env)) Maybe SolverReportErrCtxt
mb_ctxt
; UnitState
unit_state <- HasDebugCallStack => HscEnv -> UnitState
hsc_units forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
; HoleFitDispConfig
hfdc <- TcM HoleFitDispConfig
getHoleFitDispConfig
; let
err_info :: ErrInfo
err_info =
SDoc -> SDoc -> ErrInfo
ErrInfo
(forall a. a -> Maybe a -> a
fromMaybe SDoc
empty Maybe SDoc
mb_context)
([SDoc] -> SDoc
vcat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (HoleFitDispConfig -> SolverReportSupplementary -> SDoc
pprSolverReportSupplementary HoleFitDispConfig
hfdc) [SolverReportSupplementary]
supplementary)
; SrcSpan -> TcRnMessage -> TcM (MsgEnvelope TcRnMessage)
mkTcRnMessage
(RealSrcSpan -> Maybe BufSpan -> SrcSpan
RealSrcSpan (TcLclEnv -> RealSrcSpan
tcl_loc TcLclEnv
tcl_env) forall a. Maybe a
Strict.Nothing)
(UnitState -> TcRnMessageDetailed -> TcRnMessage
TcRnMessageWithInfo UnitState
unit_state forall a b. (a -> b) -> a -> b
$ ErrInfo -> TcRnMessage -> TcRnMessageDetailed
TcRnMessageDetailed ErrInfo
err_info TcRnMessage
msg) }
pprSolverReportSupplementary :: HoleFitDispConfig -> SolverReportSupplementary -> SDoc
pprSolverReportSupplementary :: HoleFitDispConfig -> SolverReportSupplementary -> SDoc
pprSolverReportSupplementary HoleFitDispConfig
hfdc = \case
SupplementaryBindings RelevantBindings
binds -> RelevantBindings -> SDoc
pprRelevantBindings RelevantBindings
binds
SupplementaryHoleFits ValidHoleFits
fits -> HoleFitDispConfig -> ValidHoleFits -> SDoc
pprValidHoleFits HoleFitDispConfig
hfdc ValidHoleFits
fits
SupplementaryCts [(Type, RealSrcSpan)]
cts -> [(Type, RealSrcSpan)] -> SDoc
pprConstraintsInclude [(Type, RealSrcSpan)]
cts
pprValidHoleFits :: HoleFitDispConfig -> ValidHoleFits -> SDoc
pprValidHoleFits :: HoleFitDispConfig -> ValidHoleFits -> SDoc
pprValidHoleFits HoleFitDispConfig
hfdc (ValidHoleFits (Fits [HoleFit]
fits Bool
discarded_fits) (Fits [HoleFit]
refs Bool
discarded_refs))
= SDoc
fits_msg SDoc -> SDoc -> SDoc
$$ SDoc
refs_msg
where
fits_msg, refs_msg, fits_discard_msg, refs_discard_msg :: SDoc
fits_msg :: SDoc
fits_msg = Bool -> SDoc -> SDoc
ppUnless (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [HoleFit]
fits) forall a b. (a -> b) -> a -> b
$
SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"Valid hole fits include") Int
2 forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat (forall a b. (a -> b) -> [a] -> [b]
map (HoleFitDispConfig -> HoleFit -> SDoc
pprHoleFit HoleFitDispConfig
hfdc) [HoleFit]
fits)
SDoc -> SDoc -> SDoc
$$ Bool -> SDoc -> SDoc
ppWhen Bool
discarded_fits SDoc
fits_discard_msg
refs_msg :: SDoc
refs_msg = Bool -> SDoc -> SDoc
ppUnless (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [HoleFit]
refs) forall a b. (a -> b) -> a -> b
$
SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"Valid refinement hole fits include") Int
2 forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat (forall a b. (a -> b) -> [a] -> [b]
map (HoleFitDispConfig -> HoleFit -> SDoc
pprHoleFit HoleFitDispConfig
hfdc) [HoleFit]
refs)
SDoc -> SDoc -> SDoc
$$ Bool -> SDoc -> SDoc
ppWhen Bool
discarded_refs SDoc
refs_discard_msg
fits_discard_msg :: SDoc
fits_discard_msg =
String -> SDoc
text String
"(Some hole fits suppressed;" SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"use -fmax-valid-hole-fits=N" SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"or -fno-max-valid-hole-fits)"
refs_discard_msg :: SDoc
refs_discard_msg =
String -> SDoc
text String
"(Some refinement hole fits suppressed;" SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"use -fmax-refinement-hole-fits=N" SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"or -fno-max-refinement-hole-fits)"
pprConstraintsInclude :: [(PredType, RealSrcSpan)] -> SDoc
pprConstraintsInclude :: [(Type, RealSrcSpan)] -> SDoc
pprConstraintsInclude [(Type, RealSrcSpan)]
cts
= Bool -> SDoc -> SDoc
ppUnless (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Type, RealSrcSpan)]
cts) forall a b. (a -> b) -> a -> b
$
SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
text String
"Constraints include")
Int
2 ([SDoc] -> SDoc
vcat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall {a} {a}. (Outputable a, Outputable a) => (a, a) -> SDoc
pprConstraint [(Type, RealSrcSpan)]
cts)
where
pprConstraint :: (a, a) -> SDoc
pprConstraint (a
constraint, a
loc) =
forall a. Outputable a => a -> SDoc
ppr a
constraint SDoc -> SDoc -> SDoc
<+> Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc
parens (String -> SDoc
text String
"from" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr a
loc))
mkIrredErr :: SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkIrredErr :: SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkIrredErr SolverReportErrCtxt
ctxt [ErrorItem]
items
= do { (SolverReportErrCtxt
ctxt, RelevantBindings
binds_msg, ErrorItem
item1) <- Bool
-> SolverReportErrCtxt
-> ErrorItem
-> TcM (SolverReportErrCtxt, RelevantBindings, ErrorItem)
relevantBindings Bool
True SolverReportErrCtxt
ctxt ErrorItem
item1
; let msg :: SolverReport
msg = SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt forall a b. (a -> b) -> a -> b
$
[Implication]
-> NonEmpty ErrorItem -> Maybe CND_Extra -> TcSolverReportMsg
CouldNotDeduce (SolverReportErrCtxt -> [Implication]
getUserGivens SolverReportErrCtxt
ctxt) (ErrorItem
item1 forall a. a -> [a] -> NonEmpty a
:| [ErrorItem]
others) forall a. Maybe a
Nothing
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SolverReport
msg forall a. Monoid a => a -> a -> a
`mappend` RelevantBindings -> SolverReport
mk_relevant_bindings RelevantBindings
binds_msg }
where
(ErrorItem
item1:[ErrorItem]
others) = [ErrorItem]
final_items
filtered_items :: [ErrorItem]
filtered_items = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorItem -> Bool
ei_suppress) [ErrorItem]
items
final_items :: [ErrorItem]
final_items | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ErrorItem]
filtered_items = [ErrorItem]
items
| Bool
otherwise = [ErrorItem]
filtered_items
mkHoleError :: NameEnv Type -> [ErrorItem] -> SolverReportErrCtxt -> Hole -> TcM (MsgEnvelope TcRnMessage)
mkHoleError :: NameEnv Type
-> [ErrorItem]
-> SolverReportErrCtxt
-> Hole
-> TcM (MsgEnvelope TcRnMessage)
mkHoleError NameEnv Type
_ [ErrorItem]
_tidy_simples SolverReportErrCtxt
ctxt hole :: Hole
hole@(Hole { hole_occ :: Hole -> OccName
hole_occ = OccName
occ, hole_loc :: Hole -> CtLoc
hole_loc = CtLoc
ct_loc })
| Hole -> Bool
isOutOfScopeHole Hole
hole
= do { DynFlags
dflags <- forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
; GlobalRdrEnv
rdr_env <- TcRn GlobalRdrEnv
getGlobalRdrEnv
; ImportAvails
imp_info <- TcRn ImportAvails
getImports
; Module
curr_mod <- forall (m :: * -> *). HasModule m => m Module
getModule
; HomePackageTable
hpt <- forall gbl lcl. TcRnIf gbl lcl HomePackageTable
getHpt
; let ([ImportError]
imp_errs, [GhcHint]
hints)
= WhatLooking
-> DynFlags
-> HomePackageTable
-> Module
-> GlobalRdrEnv
-> LocalRdrEnv
-> ImportAvails
-> RdrName
-> ([ImportError], [GhcHint])
unknownNameSuggestions WhatLooking
WL_Anything
DynFlags
dflags HomePackageTable
hpt Module
curr_mod GlobalRdrEnv
rdr_env
(TcLclEnv -> LocalRdrEnv
tcl_rdr TcLclEnv
lcl_env) ImportAvails
imp_info (OccName -> RdrName
mkRdrUnqual OccName
occ)
errs :: [SolverReportWithCtxt]
errs = [SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt (Hole -> HoleError -> TcSolverReportMsg
ReportHoleError Hole
hole forall a b. (a -> b) -> a -> b
$ [ImportError] -> HoleError
OutOfScopeHole [ImportError]
imp_errs)]
report :: SolverReport
report = [SolverReportWithCtxt]
-> [SolverReportSupplementary] -> [GhcHint] -> SolverReport
SolverReport [SolverReportWithCtxt]
errs [] [GhcHint]
hints
; SolverReportErrCtxt -> Hole -> SolverReport -> TcM ()
maybeAddDeferredBindings SolverReportErrCtxt
ctxt Hole
hole SolverReport
report
; TcLclEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport TcLclEnv
lcl_env ([SolverReportWithCtxt]
-> DiagnosticReason -> [GhcHint] -> TcRnMessage
TcRnSolverReport [SolverReportWithCtxt]
errs (SolverReportErrCtxt -> DiagnosticReason
cec_out_of_scope_holes SolverReportErrCtxt
ctxt) [GhcHint]
hints) forall a. Maybe a
Nothing []
}
where
lcl_env :: TcLclEnv
lcl_env = CtLoc -> TcLclEnv
ctLocEnv CtLoc
ct_loc
mkHoleError NameEnv Type
lcl_name_cache [ErrorItem]
tidy_simples SolverReportErrCtxt
ctxt
hole :: Hole
hole@(Hole { hole_ty :: Hole -> Type
hole_ty = Type
hole_ty
, hole_sort :: Hole -> HoleSort
hole_sort = HoleSort
sort
, hole_loc :: Hole -> CtLoc
hole_loc = CtLoc
ct_loc })
= do { RelevantBindings
rel_binds
<- Bool
-> TcLclEnv -> NameEnv Type -> TyCoVarSet -> TcM RelevantBindings
relevant_bindings Bool
False TcLclEnv
lcl_env NameEnv Type
lcl_name_cache (Type -> TyCoVarSet
tyCoVarsOfType Type
hole_ty)
; Bool
show_hole_constraints <- forall gbl lcl. GeneralFlag -> TcRnIf gbl lcl Bool
goptM GeneralFlag
Opt_ShowHoleConstraints
; let relevant_cts :: [(Type, RealSrcSpan)]
relevant_cts
| ExprHole HoleExprRef
_ <- HoleSort
sort, Bool
show_hole_constraints
= SolverReportErrCtxt -> [(Type, RealSrcSpan)]
givenConstraints SolverReportErrCtxt
ctxt
| Bool
otherwise
= []
; Bool
show_valid_hole_fits <- forall gbl lcl. GeneralFlag -> TcRnIf gbl lcl Bool
goptM GeneralFlag
Opt_ShowValidHoleFits
; (SolverReportErrCtxt
ctxt, ValidHoleFits
hole_fits) <- if Bool
show_valid_hole_fits
then SolverReportErrCtxt
-> [ErrorItem] -> Hole -> TcM (SolverReportErrCtxt, ValidHoleFits)
validHoleFits SolverReportErrCtxt
ctxt [ErrorItem]
tidy_simples Hole
hole
else forall (m :: * -> *) a. Monad m => a -> m a
return (SolverReportErrCtxt
ctxt, ValidHoleFits
noValidHoleFits)
; ([(SkolemInfoAnon, [TcId])]
grouped_skvs, [TcId]
other_tvs) <- Type -> TcM ([(SkolemInfoAnon, [TcId])], [TcId])
zonkAndGroupSkolTvs Type
hole_ty
; let reason :: DiagnosticReason
reason | ExprHole HoleExprRef
_ <- HoleSort
sort = SolverReportErrCtxt -> DiagnosticReason
cec_expr_holes SolverReportErrCtxt
ctxt
| Bool
otherwise = SolverReportErrCtxt -> DiagnosticReason
cec_type_holes SolverReportErrCtxt
ctxt
errs :: [SolverReportWithCtxt]
errs = [SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt forall a b. (a -> b) -> a -> b
$ Hole -> HoleError -> TcSolverReportMsg
ReportHoleError Hole
hole forall a b. (a -> b) -> a -> b
$ HoleSort -> [TcId] -> [(SkolemInfoAnon, [TcId])] -> HoleError
HoleError HoleSort
sort [TcId]
other_tvs [(SkolemInfoAnon, [TcId])]
grouped_skvs]
supp :: [SolverReportSupplementary]
supp = [ RelevantBindings -> SolverReportSupplementary
SupplementaryBindings RelevantBindings
rel_binds
, [(Type, RealSrcSpan)] -> SolverReportSupplementary
SupplementaryCts [(Type, RealSrcSpan)]
relevant_cts
, ValidHoleFits -> SolverReportSupplementary
SupplementaryHoleFits ValidHoleFits
hole_fits ]
; SolverReportErrCtxt -> Hole -> SolverReport -> TcM ()
maybeAddDeferredBindings SolverReportErrCtxt
ctxt Hole
hole ([SolverReportWithCtxt]
-> [SolverReportSupplementary] -> [GhcHint] -> SolverReport
SolverReport [SolverReportWithCtxt]
errs [SolverReportSupplementary]
supp [])
; TcLclEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport TcLclEnv
lcl_env ([SolverReportWithCtxt]
-> DiagnosticReason -> [GhcHint] -> TcRnMessage
TcRnSolverReport [SolverReportWithCtxt]
errs DiagnosticReason
reason [GhcHint]
noHints) (forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt) [SolverReportSupplementary]
supp
}
where
lcl_env :: TcLclEnv
lcl_env = CtLoc -> TcLclEnv
ctLocEnv CtLoc
ct_loc
zonkAndGroupSkolTvs :: Type -> TcM ([(SkolemInfoAnon, [TcTyVar])], [TcTyVar])
zonkAndGroupSkolTvs :: Type -> TcM ([(SkolemInfoAnon, [TcId])], [TcId])
zonkAndGroupSkolTvs Type
hole_ty = do
[(SkolemInfoAnon, [TcId])]
zonked_info <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\(SkolemInfo
sk, [(TcId, Int)]
tv) -> (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (SkolemInfoAnon -> IOEnv (Env TcGblEnv TcLclEnv) SkolemInfoAnon
zonkSkolemInfoAnon forall b c a. (b -> c) -> (a -> b) -> a -> c
. SkolemInfo -> SkolemInfoAnon
getSkolemInfo forall a b. (a -> b) -> a -> b
$ SkolemInfo
sk) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(TcId, Int)]
tv)) [(SkolemInfo, [(TcId, Int)])]
skolem_list
forall (m :: * -> *) a. Monad m => a -> m a
return ([(SkolemInfoAnon, [TcId])]
zonked_info, [TcId]
other_tvs)
where
tvs :: [TcId]
tvs = Type -> [TcId]
tyCoVarsOfTypeList Type
hole_ty
([TcId]
skol_tvs, [TcId]
other_tvs) = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (\TcId
tv -> TcId -> Bool
isTcTyVar TcId
tv Bool -> Bool -> Bool
&& TcId -> Bool
isSkolemTyVar TcId
tv) [TcId]
tvs
group_skolems :: UM.UniqMap SkolemInfo ([(TcTyVar, Int)])
group_skolems :: UniqMap SkolemInfo [(TcId, Int)]
group_skolems = forall a. Bag a -> [a]
bagToList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k a. Uniquable k => (a -> a -> a) -> [(k, a)] -> UniqMap k a
UM.listToUniqMap_C forall a. Bag a -> Bag a -> Bag a
unionBags [(TcId -> SkolemInfo
skolemSkolInfo TcId
tv, forall a. a -> Bag a
unitBag (TcId
tv, Int
n)) | TcId
tv <- [TcId]
skol_tvs | Int
n <- [Int
0..]]
skolem_list :: [(SkolemInfo, [(TcId, Int)])]
skolem_list = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (forall a. Ord a => [a] -> [a]
sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd)) (forall k a. UniqMap k a -> [(k, a)]
UM.nonDetEltsUniqMap UniqMap SkolemInfo [(TcId, Int)]
group_skolems)
maybeAddDeferredBindings :: SolverReportErrCtxt
-> Hole
-> SolverReport
-> TcM ()
maybeAddDeferredBindings :: SolverReportErrCtxt -> Hole -> SolverReport -> TcM ()
maybeAddDeferredBindings SolverReportErrCtxt
ctxt Hole
hole SolverReport
report = do
case Hole -> HoleSort
hole_sort Hole
hole of
ExprHole (HER IORef EvTerm
ref Type
ref_ty Unique
_) -> do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (SolverReportErrCtxt -> Bool
deferringAnyBindings SolverReportErrCtxt
ctxt) forall a b. (a -> b) -> a -> b
$ do
EvTerm
err_tm <- SolverReportErrCtxt -> CtLoc -> Type -> SolverReport -> TcM EvTerm
mkErrorTerm SolverReportErrCtxt
ctxt (Hole -> CtLoc
hole_loc Hole
hole) Type
ref_ty SolverReport
report
forall a env. IORef a -> a -> IOEnv env ()
writeMutVar IORef EvTerm
ref EvTerm
err_tm
HoleSort
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
validHoleFits :: SolverReportErrCtxt
-> [ErrorItem]
-> Hole
-> TcM (SolverReportErrCtxt, ValidHoleFits)
validHoleFits :: SolverReportErrCtxt
-> [ErrorItem] -> Hole -> TcM (SolverReportErrCtxt, ValidHoleFits)
validHoleFits ctxt :: SolverReportErrCtxt
ctxt@(CEC { cec_encl :: SolverReportErrCtxt -> [Implication]
cec_encl = [Implication]
implics
, cec_tidy :: SolverReportErrCtxt -> TidyEnv
cec_tidy = TidyEnv
lcl_env}) [ErrorItem]
simps Hole
hole
= do { (TidyEnv
tidy_env, ValidHoleFits
fits) <- TidyEnv
-> [Implication]
-> [CtEvidence]
-> Hole
-> TcM (TidyEnv, ValidHoleFits)
findValidHoleFits TidyEnv
lcl_env [Implication]
implics (forall a b. (a -> b) -> [a] -> [b]
map ErrorItem -> CtEvidence
mk_wanted [ErrorItem]
simps) Hole
hole
; forall (m :: * -> *) a. Monad m => a -> m a
return (SolverReportErrCtxt
ctxt {cec_tidy :: TidyEnv
cec_tidy = TidyEnv
tidy_env}, ValidHoleFits
fits) }
where
mk_wanted :: ErrorItem -> CtEvidence
mk_wanted :: ErrorItem -> CtEvidence
mk_wanted (EI { ei_pred :: ErrorItem -> Type
ei_pred = Type
pred, ei_evdest :: ErrorItem -> Maybe TcEvDest
ei_evdest = Just TcEvDest
dest, ei_loc :: ErrorItem -> CtLoc
ei_loc = CtLoc
loc })
= CtWanted { ctev_pred :: Type
ctev_pred = Type
pred
, ctev_dest :: TcEvDest
ctev_dest = TcEvDest
dest
, ctev_loc :: CtLoc
ctev_loc = CtLoc
loc
, ctev_rewriters :: RewriterSet
ctev_rewriters = RewriterSet
emptyRewriterSet }
mk_wanted ErrorItem
item = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"validHoleFits no evdest" (forall a. Outputable a => a -> SDoc
ppr ErrorItem
item)
givenConstraints :: SolverReportErrCtxt -> [(Type, RealSrcSpan)]
givenConstraints :: SolverReportErrCtxt -> [(Type, RealSrcSpan)]
givenConstraints SolverReportErrCtxt
ctxt
= do { implic :: Implication
implic@Implic{ ic_given :: Implication -> [TcId]
ic_given = [TcId]
given } <- SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt
; TcId
constraint <- [TcId]
given
; forall (m :: * -> *) a. Monad m => a -> m a
return (TcId -> Type
varType TcId
constraint, TcLclEnv -> RealSrcSpan
tcl_loc (Implication -> TcLclEnv
ic_env Implication
implic)) }
mkIPErr :: SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkIPErr :: SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkIPErr SolverReportErrCtxt
ctxt [ErrorItem]
items
= do { (SolverReportErrCtxt
ctxt, RelevantBindings
binds_msg, ErrorItem
item1) <- Bool
-> SolverReportErrCtxt
-> ErrorItem
-> TcM (SolverReportErrCtxt, RelevantBindings, ErrorItem)
relevantBindings Bool
True SolverReportErrCtxt
ctxt ErrorItem
item1
; let msg :: SolverReport
msg = SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt forall a b. (a -> b) -> a -> b
$ NonEmpty ErrorItem -> TcSolverReportMsg
UnboundImplicitParams (ErrorItem
item1 forall a. a -> [a] -> NonEmpty a
:| [ErrorItem]
others)
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SolverReport
msg forall a. Monoid a => a -> a -> a
`mappend` RelevantBindings -> SolverReport
mk_relevant_bindings RelevantBindings
binds_msg }
where
ErrorItem
item1:[ErrorItem]
others = [ErrorItem]
items
mkFRRErr :: HasDebugCallStack => SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkFRRErr :: HasDebugCallStack =>
SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkFRRErr SolverReportErrCtxt
ctxt [ErrorItem]
items
= do {
; (TidyEnv
_tidy_env, [FixedRuntimeRepErrorInfo]
frr_infos) <-
TidyEnv
-> [FixedRuntimeRepErrorInfo]
-> TcM (TidyEnv, [FixedRuntimeRepErrorInfo])
zonkTidyFRRInfos (SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt) forall a b. (a -> b) -> a -> b
$
forall a. (a -> a -> Ordering) -> [a] -> [a]
nubOrdBy (Type -> Type -> Ordering
nonDetCmpType forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (FixedRuntimeRepOrigin -> Type
frr_type forall b c a. (b -> c) -> (a -> b) -> a -> c
. FixedRuntimeRepErrorInfo -> FixedRuntimeRepOrigin
frr_info_origin)) forall a b. (a -> b) -> a -> b
$
forall a b. (a -> b) -> [a] -> [b]
map (forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"mkFRRErr" forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasDebugCallStack => ErrorItem -> Maybe FixedRuntimeRepErrorInfo
fixedRuntimeRepOrigin_maybe)
[ErrorItem]
items
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt forall a b. (a -> b) -> a -> b
$ [FixedRuntimeRepErrorInfo] -> TcSolverReportMsg
FixedRuntimeRepError [FixedRuntimeRepErrorInfo]
frr_infos }
fixedRuntimeRepOrigin_maybe :: HasDebugCallStack => ErrorItem -> Maybe FixedRuntimeRepErrorInfo
fixedRuntimeRepOrigin_maybe :: HasDebugCallStack => ErrorItem -> Maybe FixedRuntimeRepErrorInfo
fixedRuntimeRepOrigin_maybe ErrorItem
item
| FRROrigin FixedRuntimeRepOrigin
frr_orig <- ErrorItem -> CtOrigin
errorItemOrigin ErrorItem
item
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ FRR_Info { frr_info_origin :: FixedRuntimeRepOrigin
frr_info_origin = FixedRuntimeRepOrigin
frr_orig
, frr_info_not_concrete :: Maybe (TcId, Type)
frr_info_not_concrete = forall a. Maybe a
Nothing }
| Bool
otherwise
= forall a. Maybe a
Nothing
mkEqErr :: SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkEqErr :: SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkEqErr SolverReportErrCtxt
ctxt [ErrorItem]
items
| ErrorItem
item:[ErrorItem]
_ <- forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorItem -> Bool
ei_suppress) [ErrorItem]
items
= SolverReportErrCtxt -> ErrorItem -> TcM SolverReport
mkEqErr1 SolverReportErrCtxt
ctxt ErrorItem
item
| ErrorItem
item:[ErrorItem]
_ <- [ErrorItem]
items
= SolverReportErrCtxt -> ErrorItem -> TcM SolverReport
mkEqErr1 SolverReportErrCtxt
ctxt ErrorItem
item
| Bool
otherwise
= forall a. String -> a
panic String
"mkEqErr"
mkEqErr1 :: SolverReportErrCtxt -> ErrorItem -> TcM SolverReport
mkEqErr1 :: SolverReportErrCtxt -> ErrorItem -> TcM SolverReport
mkEqErr1 SolverReportErrCtxt
ctxt ErrorItem
item
= do { (SolverReportErrCtxt
ctxt, RelevantBindings
binds_msg, ErrorItem
item) <- Bool
-> SolverReportErrCtxt
-> ErrorItem
-> TcM (SolverReportErrCtxt, RelevantBindings, ErrorItem)
relevantBindings Bool
True SolverReportErrCtxt
ctxt ErrorItem
item
; GlobalRdrEnv
rdr_env <- TcRn GlobalRdrEnv
getGlobalRdrEnv
; FamInstEnvs
fam_envs <- TcM FamInstEnvs
tcGetFamInstEnvs
; let mb_coercible_msg :: Maybe TcSolverReportInfo
mb_coercible_msg = case ErrorItem -> EqRel
errorItemEqRel ErrorItem
item of
EqRel
NomEq -> forall a. Maybe a
Nothing
EqRel
ReprEq -> CoercibleMsg -> TcSolverReportInfo
ReportCoercibleMsg forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GlobalRdrEnv -> FamInstEnvs -> Type -> Type -> Maybe CoercibleMsg
mkCoercibleExplanation GlobalRdrEnv
rdr_env FamInstEnvs
fam_envs Type
ty1 Type
ty2
; String -> SDoc -> TcM ()
traceTc String
"mkEqErr1" (forall a. Outputable a => a -> SDoc
ppr ErrorItem
item SDoc -> SDoc -> SDoc
$$ CtOrigin -> SDoc
pprCtOrigin (ErrorItem -> CtOrigin
errorItemOrigin ErrorItem
item))
; (TcSolverReportMsg
last_msg :| [TcSolverReportMsg]
prev_msgs, [GhcHint]
hints) <- SolverReportErrCtxt
-> ErrorItem -> Type -> Type -> TcM (AccReportMsgs, [GhcHint])
mkEqErr_help SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2
; let
report :: SolverReport
report = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt) (forall a. [a] -> [a]
reverse [TcSolverReportMsg]
prev_msgs)
forall a. Monoid a => a -> a -> a
`mappend` (SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt forall a b. (a -> b) -> a -> b
$ TcSolverReportMsg -> [TcSolverReportInfo] -> TcSolverReportMsg
mkTcReportWithInfo TcSolverReportMsg
last_msg forall a b. (a -> b) -> a -> b
$ forall a. Maybe a -> [a]
maybeToList Maybe TcSolverReportInfo
mb_coercible_msg)
forall a. Monoid a => a -> a -> a
`mappend` (RelevantBindings -> SolverReport
mk_relevant_bindings RelevantBindings
binds_msg)
forall a. Monoid a => a -> a -> a
`mappend` ([GhcHint] -> SolverReport
mk_report_hints [GhcHint]
hints)
; forall (m :: * -> *) a. Monad m => a -> m a
return SolverReport
report }
where
(Type
ty1, Type
ty2) = Type -> (Type, Type)
getEqPredTys (ErrorItem -> Type
errorItemPred ErrorItem
item)
mkCoercibleExplanation :: GlobalRdrEnv -> FamInstEnvs
-> TcType -> TcType -> Maybe CoercibleMsg
mkCoercibleExplanation :: GlobalRdrEnv -> FamInstEnvs -> Type -> Type -> Maybe CoercibleMsg
mkCoercibleExplanation GlobalRdrEnv
rdr_env FamInstEnvs
fam_envs Type
ty1 Type
ty2
| Just (TyCon
tc, [Type]
tys) <- HasCallStack => Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
ty1
, (TyCon
rep_tc, [Type]
_, TcCoercionN
_) <- FamInstEnvs -> TyCon -> [Type] -> (TyCon, [Type], TcCoercionN)
tcLookupDataFamInst FamInstEnvs
fam_envs TyCon
tc [Type]
tys
, Just CoercibleMsg
msg <- TyCon -> Maybe CoercibleMsg
coercible_msg_for_tycon TyCon
rep_tc
= forall a. a -> Maybe a
Just CoercibleMsg
msg
| Just (TyCon
tc, [Type]
tys) <- HasDebugCallStack => Type -> Maybe (TyCon, [Type])
splitTyConApp_maybe Type
ty2
, (TyCon
rep_tc, [Type]
_, TcCoercionN
_) <- FamInstEnvs -> TyCon -> [Type] -> (TyCon, [Type], TcCoercionN)
tcLookupDataFamInst FamInstEnvs
fam_envs TyCon
tc [Type]
tys
, Just CoercibleMsg
msg <- TyCon -> Maybe CoercibleMsg
coercible_msg_for_tycon TyCon
rep_tc
= forall a. a -> Maybe a
Just CoercibleMsg
msg
| Just (Type
s1, Type
_) <- Type -> Maybe (Type, Type)
tcSplitAppTy_maybe Type
ty1
, Just (Type
s2, Type
_) <- Type -> Maybe (Type, Type)
tcSplitAppTy_maybe Type
ty2
, Type
s1 Type -> Type -> Bool
`eqType` Type
s2
, Type -> Bool
has_unknown_roles Type
s1
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Type -> CoercibleMsg
UnknownRoles Type
s1
| Bool
otherwise
= forall a. Maybe a
Nothing
where
coercible_msg_for_tycon :: TyCon -> Maybe CoercibleMsg
coercible_msg_for_tycon TyCon
tc
| TyCon -> Bool
isAbstractTyCon TyCon
tc
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ TyCon -> CoercibleMsg
TyConIsAbstract TyCon
tc
| TyCon -> Bool
isNewTyCon TyCon
tc
, [DataCon
data_con] <- TyCon -> [DataCon]
tyConDataCons TyCon
tc
, let dc_name :: Name
dc_name = DataCon -> Name
dataConName DataCon
data_con
, forall a. Maybe a -> Bool
isNothing (GlobalRdrEnv -> Name -> Maybe GlobalRdrElt
lookupGRE_Name GlobalRdrEnv
rdr_env Name
dc_name)
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ TyCon -> DataCon -> CoercibleMsg
OutOfScopeNewtypeConstructor TyCon
tc DataCon
data_con
| Bool
otherwise = forall a. Maybe a
Nothing
has_unknown_roles :: Type -> Bool
has_unknown_roles Type
ty
| Just (TyCon
tc, [Type]
tys) <- HasCallStack => Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
ty
= [Type]
tys forall a. [a] -> Int -> Bool
`lengthAtLeast` TyCon -> Int
tyConArity TyCon
tc
| Just (Type
s, Type
_) <- Type -> Maybe (Type, Type)
tcSplitAppTy_maybe Type
ty
= Type -> Bool
has_unknown_roles Type
s
| Type -> Bool
isTyVarTy Type
ty
= Bool
True
| Bool
otherwise
= Bool
False
type AccReportMsgs = NonEmpty TcSolverReportMsg
mkEqErr_help :: SolverReportErrCtxt
-> ErrorItem
-> TcType -> TcType -> TcM (AccReportMsgs, [GhcHint])
mkEqErr_help :: SolverReportErrCtxt
-> ErrorItem -> Type -> Type -> TcM (AccReportMsgs, [GhcHint])
mkEqErr_help SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2
| Just (TcId, TcCoercionN)
casted_tv1 <- Type -> Maybe (TcId, TcCoercionN)
tcGetCastedTyVar_maybe Type
ty1
= SolverReportErrCtxt
-> ErrorItem
-> (TcId, TcCoercionN)
-> Type
-> TcM (AccReportMsgs, [GhcHint])
mkTyVarEqErr SolverReportErrCtxt
ctxt ErrorItem
item (TcId, TcCoercionN)
casted_tv1 Type
ty2
| Just (TcId, TcCoercionN)
casted_tv2 <- Type -> Maybe (TcId, TcCoercionN)
tcGetCastedTyVar_maybe Type
ty2
= SolverReportErrCtxt
-> ErrorItem
-> (TcId, TcCoercionN)
-> Type
-> TcM (AccReportMsgs, [GhcHint])
mkTyVarEqErr SolverReportErrCtxt
ctxt ErrorItem
item (TcId, TcCoercionN)
casted_tv2 Type
ty1
| Bool
otherwise
= forall (m :: * -> *) a. Monad m => a -> m a
return (SolverReportErrCtxt
-> ErrorItem -> Type -> Type -> TcSolverReportMsg
reportEqErr SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2 forall a. a -> [a] -> NonEmpty a
:| [], [])
reportEqErr :: SolverReportErrCtxt
-> ErrorItem
-> TcType -> TcType -> TcSolverReportMsg
reportEqErr :: SolverReportErrCtxt
-> ErrorItem -> Type -> Type -> TcSolverReportMsg
reportEqErr SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2
= TcSolverReportMsg -> [TcSolverReportInfo] -> TcSolverReportMsg
mkTcReportWithInfo TcSolverReportMsg
mismatch [TcSolverReportInfo]
eqInfos
where
mismatch :: TcSolverReportMsg
mismatch = Bool
-> SolverReportErrCtxt
-> ErrorItem
-> Type
-> Type
-> TcSolverReportMsg
misMatchOrCND Bool
False SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2
eqInfos :: [TcSolverReportInfo]
eqInfos = Type -> Type -> [TcSolverReportInfo]
eqInfoMsgs Type
ty1 Type
ty2
mkTyVarEqErr :: SolverReportErrCtxt -> ErrorItem
-> (TcTyVar, TcCoercionN) -> TcType -> TcM (AccReportMsgs, [GhcHint])
mkTyVarEqErr :: SolverReportErrCtxt
-> ErrorItem
-> (TcId, TcCoercionN)
-> Type
-> TcM (AccReportMsgs, [GhcHint])
mkTyVarEqErr SolverReportErrCtxt
ctxt ErrorItem
item (TcId, TcCoercionN)
casted_tv1 Type
ty2
= do { String -> SDoc -> TcM ()
traceTc String
"mkTyVarEqErr" (forall a. Outputable a => a -> SDoc
ppr ErrorItem
item SDoc -> SDoc -> SDoc
$$ forall a. Outputable a => a -> SDoc
ppr (TcId, TcCoercionN)
casted_tv1 SDoc -> SDoc -> SDoc
$$ forall a. Outputable a => a -> SDoc
ppr Type
ty2)
; SolverReportErrCtxt
-> ErrorItem
-> (TcId, TcCoercionN)
-> Type
-> TcM (AccReportMsgs, [GhcHint])
mkTyVarEqErr' SolverReportErrCtxt
ctxt ErrorItem
item (TcId, TcCoercionN)
casted_tv1 Type
ty2 }
mkTyVarEqErr' :: SolverReportErrCtxt -> ErrorItem
-> (TcTyVar, TcCoercionN) -> TcType -> TcM (AccReportMsgs, [GhcHint])
mkTyVarEqErr' :: SolverReportErrCtxt
-> ErrorItem
-> (TcId, TcCoercionN)
-> Type
-> TcM (AccReportMsgs, [GhcHint])
mkTyVarEqErr' SolverReportErrCtxt
ctxt ErrorItem
item (TcId
tv1, TcCoercionN
co1) Type
ty2
| Just FixedRuntimeRepErrorInfo
frr_info <- Maybe FixedRuntimeRepErrorInfo
mb_concrete_reason
= do
(TidyEnv
_, [FixedRuntimeRepErrorInfo]
infos) <- TidyEnv
-> [FixedRuntimeRepErrorInfo]
-> TcM (TidyEnv, [FixedRuntimeRepErrorInfo])
zonkTidyFRRInfos (SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt) [FixedRuntimeRepErrorInfo
frr_info]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FixedRuntimeRepErrorInfo] -> TcSolverReportMsg
FixedRuntimeRepError [FixedRuntimeRepErrorInfo]
infos forall a. a -> [a] -> NonEmpty a
:| [], [])
| CheckTyEqResult
check_eq_result CheckTyEqResult -> CheckTyEqProblem -> Bool
`cterHasProblem` CheckTyEqProblem
cteImpredicative
= do
[TcSolverReportInfo]
tyvar_eq_info <- TcId -> Type -> TcM [TcSolverReportInfo]
extraTyVarEqInfo TcId
tv1 Type
ty2
let
poly_msg :: TcSolverReportMsg
poly_msg = ErrorItem -> TcId -> Type -> TcSolverReportMsg
CannotUnifyWithPolytype ErrorItem
item TcId
tv1 Type
ty2
poly_msg_with_info :: TcSolverReportMsg
poly_msg_with_info
| TcId -> Bool
isSkolemTyVar TcId
tv1
= TcSolverReportMsg -> [TcSolverReportInfo] -> TcSolverReportMsg
mkTcReportWithInfo TcSolverReportMsg
poly_msg [TcSolverReportInfo]
tyvar_eq_info
| Bool
otherwise
= TcSolverReportMsg
poly_msg
forall (m :: * -> *) a. Monad m => a -> m a
return (TcSolverReportMsg
poly_msg_with_info forall a. a -> NonEmpty a -> NonEmpty a
<| TcSolverReportMsg
headline_msg forall a. a -> [a] -> NonEmpty a
:| [], [])
| TcId -> Bool
isSkolemTyVar TcId
tv1
Bool -> Bool -> Bool
|| TcId -> Bool
isTyVarTyVar TcId
tv1 Bool -> Bool -> Bool
&& Bool -> Bool
not (Type -> Bool
isTyVarTy Type
ty2)
Bool -> Bool -> Bool
|| ErrorItem -> EqRel
errorItemEqRel ErrorItem
item forall a. Eq a => a -> a -> Bool
== EqRel
ReprEq
= do
[TcSolverReportInfo]
tv_extra <- TcId -> Type -> TcM [TcSolverReportInfo]
extraTyVarEqInfo TcId
tv1 Type
ty2
forall (m :: * -> *) a. Monad m => a -> m a
return (TcSolverReportMsg -> [TcSolverReportInfo] -> TcSolverReportMsg
mkTcReportWithInfo TcSolverReportMsg
headline_msg [TcSolverReportInfo]
tv_extra forall a. a -> [a] -> NonEmpty a
:| [], [GhcHint]
add_sig)
| CheckTyEqResult -> Bool
cterHasOccursCheck CheckTyEqResult
check_eq_result
= let extras2 :: [TcSolverReportInfo]
extras2 = Type -> Type -> [TcSolverReportInfo]
eqInfoMsgs Type
ty1 Type
ty2
interesting_tyvars :: [TcId]
interesting_tyvars = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type -> Bool
noFreeVarsOfType forall b c a. (b -> c) -> (a -> b) -> a -> c
. TcId -> Type
tyVarKind) forall a b. (a -> b) -> a -> b
$
forall a. (a -> Bool) -> [a] -> [a]
filter TcId -> Bool
isTyVar forall a b. (a -> b) -> a -> b
$
FV -> [TcId]
fvVarList forall a b. (a -> b) -> a -> b
$
Type -> FV
tyCoFVsOfType Type
ty1 FV -> FV -> FV
`unionFV` Type -> FV
tyCoFVsOfType Type
ty2
extras3 :: [TcSolverReportInfo]
extras3 = case [TcId]
interesting_tyvars of
[] -> []
(TcId
tv : [TcId]
tvs) -> [NonEmpty TcId -> TcSolverReportInfo
OccursCheckInterestingTyVars (TcId
tv forall a. a -> [a] -> NonEmpty a
:| [TcId]
tvs)]
in forall (m :: * -> *) a. Monad m => a -> m a
return (TcSolverReportMsg -> [TcSolverReportInfo] -> TcSolverReportMsg
mkTcReportWithInfo TcSolverReportMsg
headline_msg ([TcSolverReportInfo]
extras2 forall a. [a] -> [a] -> [a]
++ [TcSolverReportInfo]
extras3) forall a. a -> [a] -> NonEmpty a
:| [], [])
| TcCoercionN -> Bool
hasCoercionHoleCo TcCoercionN
co1 Bool -> Bool -> Bool
|| Type -> Bool
hasCoercionHoleTy Type
ty2
= forall (m :: * -> *) a. Monad m => a -> m a
return (ErrorItem -> TcSolverReportMsg
mkBlockedEqErr ErrorItem
item forall a. a -> [a] -> NonEmpty a
:| [], [])
| (Implication
implic:[Implication]
_) <- SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt
, Implic { ic_skols :: Implication -> [TcId]
ic_skols = [TcId]
skols } <- Implication
implic
, TcId
tv1 forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [TcId]
skols
= do
[TcSolverReportInfo]
tv_extra <- TcId -> Type -> TcM [TcSolverReportInfo]
extraTyVarEqInfo TcId
tv1 Type
ty2
forall (m :: * -> *) a. Monad m => a -> m a
return (TcSolverReportMsg -> [TcSolverReportInfo] -> TcSolverReportMsg
mkTcReportWithInfo TcSolverReportMsg
mismatch_msg [TcSolverReportInfo]
tv_extra forall a. a -> [a] -> NonEmpty a
:| [], [])
| (Implication
implic:[Implication]
_) <- SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt
, Implic { ic_skols :: Implication -> [TcId]
ic_skols = [TcId]
skols } <- Implication
implic
, let esc_skols :: [TcId]
esc_skols = forall a. (a -> Bool) -> [a] -> [a]
filter (TcId -> TyCoVarSet -> Bool
`elemVarSet` (Type -> TyCoVarSet
tyCoVarsOfType Type
ty2)) [TcId]
skols
, Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TcId]
esc_skols)
= forall (m :: * -> *) a. Monad m => a -> m a
return (ErrorItem -> Implication -> [TcId] -> TcSolverReportMsg
SkolemEscape ErrorItem
item Implication
implic [TcId]
esc_skols forall a. a -> [a] -> NonEmpty a
:| [TcSolverReportMsg
mismatch_msg], [])
| (Implication
implic:[Implication]
_) <- SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt
, Implic { ic_tclvl :: Implication -> TcLevel
ic_tclvl = TcLevel
lvl } <- Implication
implic
= forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (Bool -> Bool
not (TcLevel -> TcId -> Bool
isTouchableMetaTyVar TcLevel
lvl TcId
tv1))
(forall a. Outputable a => a -> SDoc
ppr TcId
tv1 SDoc -> SDoc -> SDoc
$$ forall a. Outputable a => a -> SDoc
ppr TcLevel
lvl) forall a b. (a -> b) -> a -> b
$ do
let tclvl_extra :: TcSolverReportMsg
tclvl_extra = TcId -> Implication -> TcSolverReportMsg
UntouchableVariable TcId
tv1 Implication
implic
[TcSolverReportInfo]
tv_extra <- TcId -> Type -> TcM [TcSolverReportInfo]
extraTyVarEqInfo TcId
tv1 Type
ty2
forall (m :: * -> *) a. Monad m => a -> m a
return (TcSolverReportMsg -> [TcSolverReportInfo] -> TcSolverReportMsg
mkTcReportWithInfo TcSolverReportMsg
tclvl_extra [TcSolverReportInfo]
tv_extra forall a. a -> [a] -> NonEmpty a
:| [TcSolverReportMsg
mismatch_msg], [GhcHint]
add_sig)
| Bool
otherwise
= forall (m :: * -> *) a. Monad m => a -> m a
return (SolverReportErrCtxt
-> ErrorItem -> Type -> Type -> TcSolverReportMsg
reportEqErr SolverReportErrCtxt
ctxt ErrorItem
item (TcId -> Type
mkTyVarTy TcId
tv1) Type
ty2 forall a. a -> [a] -> NonEmpty a
:| [], [])
where
headline_msg :: TcSolverReportMsg
headline_msg = Bool
-> SolverReportErrCtxt
-> ErrorItem
-> Type
-> Type
-> TcSolverReportMsg
misMatchOrCND Bool
insoluble_occurs_check SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2
mismatch_msg :: TcSolverReportMsg
mismatch_msg = ErrorItem -> Type -> Type -> TcSolverReportMsg
mkMismatchMsg ErrorItem
item Type
ty1 Type
ty2
add_sig :: [GhcHint]
add_sig = forall a. Maybe a -> [a]
maybeToList forall a b. (a -> b) -> a -> b
$ SolverReportErrCtxt -> Type -> Type -> Maybe GhcHint
suggestAddSig SolverReportErrCtxt
ctxt Type
ty1 Type
ty2
mb_concrete_reason :: Maybe FixedRuntimeRepErrorInfo
mb_concrete_reason
| Just ConcreteTvOrigin
frr_orig <- TcId -> Maybe ConcreteTvOrigin
isConcreteTyVar_maybe TcId
tv1
, Bool -> Bool
not (Type -> Bool
isConcrete Type
ty2)
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ConcreteTvOrigin -> TcId -> Type -> FixedRuntimeRepErrorInfo
frr_reason ConcreteTvOrigin
frr_orig TcId
tv1 Type
ty2
| Just (TcId
tv2, ConcreteTvOrigin
frr_orig) <- Type -> Maybe (TcId, ConcreteTvOrigin)
isConcreteTyVarTy_maybe Type
ty2
, Bool -> Bool
not (TcId -> Bool
isConcreteTyVar TcId
tv1)
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ConcreteTvOrigin -> TcId -> Type -> FixedRuntimeRepErrorInfo
frr_reason ConcreteTvOrigin
frr_orig TcId
tv2 Type
ty1
| Bool
otherwise
= forall a. Maybe a
Nothing
frr_reason :: ConcreteTvOrigin -> TcId -> Type -> FixedRuntimeRepErrorInfo
frr_reason (ConcreteFRR FixedRuntimeRepOrigin
frr_orig) TcId
conc_tv Type
not_conc
= FRR_Info { frr_info_origin :: FixedRuntimeRepOrigin
frr_info_origin = FixedRuntimeRepOrigin
frr_orig
, frr_info_not_concrete :: Maybe (TcId, Type)
frr_info_not_concrete = forall a. a -> Maybe a
Just (TcId
conc_tv, Type
not_conc) }
ty1 :: Type
ty1 = TcId -> Type
mkTyVarTy TcId
tv1
check_eq_result :: CheckTyEqResult
check_eq_result = case ErrorItem -> Maybe CtIrredReason
ei_m_reason ErrorItem
item of
Just (NonCanonicalReason CheckTyEqResult
result) -> CheckTyEqResult
result
Maybe CtIrredReason
_ -> TcId -> Type -> CheckTyEqResult
checkTyVarEq TcId
tv1 Type
ty2
insoluble_occurs_check :: Bool
insoluble_occurs_check = CheckTyEqResult
check_eq_result CheckTyEqResult -> CheckTyEqProblem -> Bool
`cterHasProblem` CheckTyEqProblem
cteInsolubleOccurs
eqInfoMsgs :: TcType -> TcType -> [TcSolverReportInfo]
eqInfoMsgs :: Type -> Type -> [TcSolverReportInfo]
eqInfoMsgs Type
ty1 Type
ty2
= forall a. [Maybe a] -> [a]
catMaybes [Maybe TcSolverReportInfo
tyfun_msg, Maybe TcSolverReportInfo
ambig_msg]
where
mb_fun1 :: Maybe TyCon
mb_fun1 = Type -> Maybe TyCon
isTyFun_maybe Type
ty1
mb_fun2 :: Maybe TyCon
mb_fun2 = Type -> Maybe TyCon
isTyFun_maybe Type
ty2
ambig_tkvs1 :: ([TcId], [TcId])
ambig_tkvs1 = forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty (\TyCon
_ -> Type -> ([TcId], [TcId])
ambigTkvsOfTy Type
ty1) Maybe TyCon
mb_fun1
ambig_tkvs2 :: ([TcId], [TcId])
ambig_tkvs2 = forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty (\TyCon
_ -> Type -> ([TcId], [TcId])
ambigTkvsOfTy Type
ty2) Maybe TyCon
mb_fun2
ambig_tkvs :: ([TcId], [TcId])
ambig_tkvs@([TcId]
ambig_kvs, [TcId]
ambig_tvs) = ([TcId], [TcId])
ambig_tkvs1 forall a. Semigroup a => a -> a -> a
S.<> ([TcId], [TcId])
ambig_tkvs2
ambig_msg :: Maybe TcSolverReportInfo
ambig_msg | forall a. Maybe a -> Bool
isJust Maybe TyCon
mb_fun1 Bool -> Bool -> Bool
|| forall a. Maybe a -> Bool
isJust Maybe TyCon
mb_fun2
, Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TcId]
ambig_kvs Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TcId]
ambig_tvs)
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Bool -> ([TcId], [TcId]) -> TcSolverReportInfo
Ambiguity Bool
False ([TcId], [TcId])
ambig_tkvs
| Bool
otherwise
= forall a. Maybe a
Nothing
tyfun_msg :: Maybe TcSolverReportInfo
tyfun_msg | Just TyCon
tc1 <- Maybe TyCon
mb_fun1
, Just TyCon
tc2 <- Maybe TyCon
mb_fun2
, TyCon
tc1 forall a. Eq a => a -> a -> Bool
== TyCon
tc2
, Bool -> Bool
not (TyCon -> Role -> Bool
isInjectiveTyCon TyCon
tc1 Role
Nominal)
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ TyCon -> TcSolverReportInfo
NonInjectiveTyFam TyCon
tc1
| Bool
otherwise
= forall a. Maybe a
Nothing
misMatchOrCND :: Bool -> SolverReportErrCtxt -> ErrorItem
-> TcType -> TcType -> TcSolverReportMsg
misMatchOrCND :: Bool
-> SolverReportErrCtxt
-> ErrorItem
-> Type
-> Type
-> TcSolverReportMsg
misMatchOrCND Bool
insoluble_occurs_check SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2
| Bool
insoluble_occurs_check
Bool -> Bool -> Bool
|| (Type -> Bool
isRigidTy Type
ty1 Bool -> Bool -> Bool
&& Type -> Bool
isRigidTy Type
ty2)
Bool -> Bool -> Bool
|| (ErrorItem -> CtFlavour
ei_flavour ErrorItem
item forall a. Eq a => a -> a -> Bool
== CtFlavour
Given)
Bool -> Bool -> Bool
|| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Implication]
givens
=
ErrorItem -> Type -> Type -> TcSolverReportMsg
mkMismatchMsg ErrorItem
item Type
ty1 Type
ty2
| Bool
otherwise
= [Implication]
-> NonEmpty ErrorItem -> Maybe CND_Extra -> TcSolverReportMsg
CouldNotDeduce [Implication]
givens (ErrorItem
item forall a. a -> [a] -> NonEmpty a
:| []) (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ TypeOrKind -> Type -> Type -> CND_Extra
CND_Extra TypeOrKind
level Type
ty1 Type
ty2)
where
level :: TypeOrKind
level = CtLoc -> Maybe TypeOrKind
ctLocTypeOrKind_maybe (ErrorItem -> CtLoc
errorItemCtLoc ErrorItem
item) forall a. Maybe a -> a -> a
`orElse` TypeOrKind
TypeLevel
givens :: [Implication]
givens = [ Implication
given | Implication
given <- SolverReportErrCtxt -> [Implication]
getUserGivens SolverReportErrCtxt
ctxt, Implication -> HasGivenEqs
ic_given_eqs Implication
given forall a. Eq a => a -> a -> Bool
/= HasGivenEqs
NoGivenEqs ]
mkBlockedEqErr :: ErrorItem -> TcSolverReportMsg
mkBlockedEqErr :: ErrorItem -> TcSolverReportMsg
mkBlockedEqErr ErrorItem
item = ErrorItem -> TcSolverReportMsg
BlockedEquality ErrorItem
item
extraTyVarEqInfo :: TcTyVar -> TcType -> TcM [TcSolverReportInfo]
TcId
tv1 Type
ty2
= (:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TcId -> TcM TcSolverReportInfo
extraTyVarInfo TcId
tv1 forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Type -> TcM [TcSolverReportInfo]
ty_extra Type
ty2
where
ty_extra :: Type -> TcM [TcSolverReportInfo]
ty_extra Type
ty = case Type -> Maybe (TcId, TcCoercionN)
tcGetCastedTyVar_maybe Type
ty of
Just (TcId
tv, TcCoercionN
_) -> (forall a. a -> [a] -> [a]
:[]) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TcId -> TcM TcSolverReportInfo
extraTyVarInfo TcId
tv
Maybe (TcId, TcCoercionN)
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return []
extraTyVarInfo :: TcTyVar -> TcM TcSolverReportInfo
TcId
tv = forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (TcId -> Bool
isTyVar TcId
tv) (forall a. Outputable a => a -> SDoc
ppr TcId
tv) forall a b. (a -> b) -> a -> b
$
case TcId -> TcTyVarDetails
tcTyVarDetails TcId
tv of
SkolemTv SkolemInfo
skol_info TcLevel
lvl Bool
overlaps -> do
SkolemInfo
new_skol_info <- SkolemInfo -> TcM SkolemInfo
zonkSkolemInfo SkolemInfo
skol_info
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ TcId -> TcSolverReportInfo
TyVarInfo (Name -> Type -> TcTyVarDetails -> TcId
mkTcTyVar (TcId -> Name
tyVarName TcId
tv) (TcId -> Type
tyVarKind TcId
tv) (SkolemInfo -> TcLevel -> Bool -> TcTyVarDetails
SkolemTv SkolemInfo
new_skol_info TcLevel
lvl Bool
overlaps))
TcTyVarDetails
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ TcId -> TcSolverReportInfo
TyVarInfo TcId
tv
suggestAddSig :: SolverReportErrCtxt -> TcType -> TcType -> Maybe GhcHint
suggestAddSig :: SolverReportErrCtxt -> Type -> Type -> Maybe GhcHint
suggestAddSig SolverReportErrCtxt
ctxt Type
ty1 Type
_ty2
| Name
bndr : [Name]
bndrs <- [Name]
inferred_bndrs
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ AvailableBindings -> GhcHint
SuggestAddTypeSignatures forall a b. (a -> b) -> a -> b
$ NonEmpty Name -> AvailableBindings
NamedBindings (Name
bndr forall a. a -> [a] -> NonEmpty a
:| [Name]
bndrs)
| Bool
otherwise
= forall a. Maybe a
Nothing
where
inferred_bndrs :: [Name]
inferred_bndrs =
case Type -> Maybe TcId
tcGetTyVar_maybe Type
ty1 of
Just TcId
tv | TcId -> Bool
isSkolemTyVar TcId
tv -> [Implication] -> Bool -> TcId -> [Name]
find (SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt) Bool
False TcId
tv
Maybe TcId
_ -> []
find :: [Implication] -> Bool -> TcId -> [Name]
find [] Bool
_ TcId
_ = []
find (Implication
implic:[Implication]
implics) Bool
seen_eqs TcId
tv
| TcId
tv forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Implication -> [TcId]
ic_skols Implication
implic
, InferSkol [(Name, Type)]
prs <- Implication -> SkolemInfoAnon
ic_info Implication
implic
, Bool
seen_eqs
= forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(Name, Type)]
prs
| Bool
otherwise
= [Implication] -> Bool -> TcId -> [Name]
find [Implication]
implics (Bool
seen_eqs Bool -> Bool -> Bool
|| Implication -> HasGivenEqs
ic_given_eqs Implication
implic forall a. Eq a => a -> a -> Bool
/= HasGivenEqs
NoGivenEqs) TcId
tv
mkMismatchMsg :: ErrorItem -> Type -> Type -> TcSolverReportMsg
mkMismatchMsg :: ErrorItem -> Type -> Type -> TcSolverReportMsg
mkMismatchMsg ErrorItem
item Type
ty1 Type
ty2 =
case CtOrigin
orig of
TypeEqOrigin { Type
uo_actual :: CtOrigin -> Type
uo_actual :: Type
uo_actual, Type
uo_expected :: CtOrigin -> Type
uo_expected :: Type
uo_expected, uo_thing :: CtOrigin -> Maybe TypedThing
uo_thing = Maybe TypedThing
mb_thing } ->
TcSolverReportMsg -> [TcSolverReportInfo] -> TcSolverReportMsg
mkTcReportWithInfo
(TypeEqMismatch
{ teq_mismatch_ppr_explicit_kinds :: Bool
teq_mismatch_ppr_explicit_kinds = Bool
ppr_explicit_kinds
, teq_mismatch_item :: ErrorItem
teq_mismatch_item = ErrorItem
item
, teq_mismatch_ty1 :: Type
teq_mismatch_ty1 = Type
ty1
, teq_mismatch_ty2 :: Type
teq_mismatch_ty2 = Type
ty2
, teq_mismatch_actual :: Type
teq_mismatch_actual = Type
uo_actual
, teq_mismatch_expected :: Type
teq_mismatch_expected = Type
uo_expected
, teq_mismatch_what :: Maybe TypedThing
teq_mismatch_what = Maybe TypedThing
mb_thing})
[TcSolverReportInfo]
extras
KindEqOrigin Type
cty1 Type
cty2 CtOrigin
sub_o Maybe TypeOrKind
mb_sub_t_or_k ->
TcSolverReportMsg -> [TcSolverReportInfo] -> TcSolverReportMsg
mkTcReportWithInfo (Bool -> ErrorItem -> Type -> Type -> TcSolverReportMsg
Mismatch Bool
False ErrorItem
item Type
ty1 Type
ty2)
(Type -> Type -> CtOrigin -> Maybe TypeOrKind -> TcSolverReportInfo
WhenMatching Type
cty1 Type
cty2 CtOrigin
sub_o Maybe TypeOrKind
mb_sub_t_or_k forall a. a -> [a] -> [a]
: [TcSolverReportInfo]
extras)
CtOrigin
_ ->
TcSolverReportMsg -> [TcSolverReportInfo] -> TcSolverReportMsg
mkTcReportWithInfo
(Bool -> ErrorItem -> Type -> Type -> TcSolverReportMsg
Mismatch Bool
False ErrorItem
item Type
ty1 Type
ty2)
[TcSolverReportInfo]
extras
where
orig :: CtOrigin
orig = ErrorItem -> CtOrigin
errorItemOrigin ErrorItem
item
extras :: [TcSolverReportInfo]
extras = Type -> Type -> [TcSolverReportInfo]
sameOccExtras Type
ty2 Type
ty1
ppr_explicit_kinds :: Bool
ppr_explicit_kinds = Type -> Type -> CtOrigin -> Bool
shouldPprWithExplicitKinds Type
ty1 Type
ty2 CtOrigin
orig
shouldPprWithExplicitKinds :: Type -> Type -> CtOrigin -> Bool
shouldPprWithExplicitKinds :: Type -> Type -> CtOrigin -> Bool
shouldPprWithExplicitKinds Type
_ty1 Type
_ty2 (TypeEqOrigin { uo_actual :: CtOrigin -> Type
uo_actual = Type
act
, uo_expected :: CtOrigin -> Type
uo_expected = Type
exp
, uo_visible :: CtOrigin -> Bool
uo_visible = Bool
vis })
| Bool -> Bool
not Bool
vis = Bool
True
| Bool
otherwise = Type -> Type -> Bool
tcEqTypeVis Type
act Type
exp
shouldPprWithExplicitKinds Type
ty1 Type
ty2 CtOrigin
_ct
= Type -> Type -> Bool
tcEqTypeVis Type
ty1 Type
ty2
sameOccExtras :: TcType -> TcType -> [TcSolverReportInfo]
Type
ty1 Type
ty2
| Just (TyCon
tc1, [Type]
_) <- HasCallStack => Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
ty1
, Just (TyCon
tc2, [Type]
_) <- HasCallStack => Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
ty2
, let n1 :: Name
n1 = TyCon -> Name
tyConName TyCon
tc1
n2 :: Name
n2 = TyCon -> Name
tyConName TyCon
tc2
same_occ :: Bool
same_occ = Name -> OccName
nameOccName Name
n1 forall a. Eq a => a -> a -> Bool
== Name -> OccName
nameOccName Name
n2
same_pkg :: Bool
same_pkg = forall unit. GenModule unit -> unit
moduleUnit (HasDebugCallStack => Name -> Module
nameModule Name
n1) forall a. Eq a => a -> a -> Bool
== forall unit. GenModule unit -> unit
moduleUnit (HasDebugCallStack => Name -> Module
nameModule Name
n2)
, Name
n1 forall a. Eq a => a -> a -> Bool
/= Name
n2
, Bool
same_occ
= [Bool -> Name -> Name -> TcSolverReportInfo
SameOcc Bool
same_pkg Name
n1 Name
n2]
| Bool
otherwise
= []
mkDictErr :: HasDebugCallStack => SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkDictErr :: HasDebugCallStack =>
SolverReportErrCtxt -> [ErrorItem] -> TcM SolverReport
mkDictErr SolverReportErrCtxt
ctxt [ErrorItem]
orig_items
= forall a. HasCallStack => Bool -> a -> a
assert (Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ErrorItem]
items)) forall a b. (a -> b) -> a -> b
$
do { InstEnvs
inst_envs <- TcM InstEnvs
tcGetInstEnvs
; let min_items :: [ErrorItem]
min_items = [ErrorItem] -> [ErrorItem]
elim_superclasses [ErrorItem]
items
lookups :: [(ErrorItem, ClsInstLookupResult)]
lookups = forall a b. (a -> b) -> [a] -> [b]
map (InstEnvs -> ErrorItem -> (ErrorItem, ClsInstLookupResult)
lookup_cls_inst InstEnvs
inst_envs) [ErrorItem]
min_items
([(ErrorItem, ClsInstLookupResult)]
no_inst_items, [(ErrorItem, ClsInstLookupResult)]
overlap_items) = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (ErrorItem, ClsInstLookupResult) -> Bool
is_no_inst [(ErrorItem, ClsInstLookupResult)]
lookups
; TcSolverReportMsg
err <- HasCallStack =>
SolverReportErrCtxt
-> (ErrorItem, ClsInstLookupResult) -> TcM TcSolverReportMsg
mk_dict_err SolverReportErrCtxt
ctxt (forall a. [a] -> a
head ([(ErrorItem, ClsInstLookupResult)]
no_inst_items forall a. [a] -> [a] -> [a]
++ [(ErrorItem, ClsInstLookupResult)]
overlap_items))
; forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt TcSolverReportMsg
err }
where
filtered_items :: [ErrorItem]
filtered_items = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorItem -> Bool
ei_suppress) [ErrorItem]
orig_items
items :: [ErrorItem]
items | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ErrorItem]
filtered_items = [ErrorItem]
orig_items
| Bool
otherwise = [ErrorItem]
filtered_items
no_givens :: Bool
no_givens = forall (t :: * -> *) a. Foldable t => t a -> Bool
null (SolverReportErrCtxt -> [Implication]
getUserGivens SolverReportErrCtxt
ctxt)
is_no_inst :: (ErrorItem, ClsInstLookupResult) -> Bool
is_no_inst (ErrorItem
item, ([InstMatch]
matches, PotentialUnifiers
unifiers, [InstMatch]
_))
= Bool
no_givens
Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => t a -> Bool
null [InstMatch]
matches
Bool -> Bool -> Bool
&& (PotentialUnifiers -> Bool
nullUnifiers PotentialUnifiers
unifiers Bool -> Bool -> Bool
|| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. TcId -> Bool
isAmbiguousTyVar) (Type -> [TcId]
tyCoVarsOfTypeList (ErrorItem -> Type
errorItemPred ErrorItem
item)))
lookup_cls_inst :: InstEnvs -> ErrorItem -> (ErrorItem, ClsInstLookupResult)
lookup_cls_inst InstEnvs
inst_envs ErrorItem
item
= (ErrorItem
item, Bool -> InstEnvs -> Class -> [Type] -> ClsInstLookupResult
lookupInstEnv Bool
True InstEnvs
inst_envs Class
clas [Type]
tys)
where
(Class
clas, [Type]
tys) = HasDebugCallStack => Type -> (Class, [Type])
getClassPredTys (ErrorItem -> Type
errorItemPred ErrorItem
item)
elim_superclasses :: [ErrorItem] -> [ErrorItem]
elim_superclasses [ErrorItem]
items = forall a. (a -> Type) -> [a] -> [a]
mkMinimalBySCs ErrorItem -> Type
errorItemPred [ErrorItem]
items
mk_dict_err :: HasCallStack => SolverReportErrCtxt -> (ErrorItem, ClsInstLookupResult)
-> TcM TcSolverReportMsg
mk_dict_err :: HasCallStack =>
SolverReportErrCtxt
-> (ErrorItem, ClsInstLookupResult) -> TcM TcSolverReportMsg
mk_dict_err SolverReportErrCtxt
ctxt (ErrorItem
item, ([InstMatch]
matches, PotentialUnifiers
unifiers, [InstMatch]
unsafe_overlapped))
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [InstMatch]
matches
= do { (SolverReportErrCtxt
_, RelevantBindings
rel_binds, ErrorItem
item) <- Bool
-> SolverReportErrCtxt
-> ErrorItem
-> TcM (SolverReportErrCtxt, RelevantBindings, ErrorItem)
relevantBindings Bool
True SolverReportErrCtxt
ctxt ErrorItem
item
; [ClsInst]
candidate_insts <- TcM [ClsInst]
get_candidate_instances
; ([ImportError]
imp_errs, [GhcHint]
field_suggestions) <- TcM ([ImportError], [GhcHint])
record_field_suggestions
; forall (m :: * -> *) a. Monad m => a -> m a
return (ErrorItem
-> [ClsInst]
-> RelevantBindings
-> [ImportError]
-> [GhcHint]
-> TcSolverReportMsg
cannot_resolve_msg ErrorItem
item [ClsInst]
candidate_insts RelevantBindings
rel_binds [ImportError]
imp_errs [GhcHint]
field_suggestions) }
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [InstMatch]
unsafe_overlapped
= forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ TcSolverReportMsg
overlap_msg
| Bool
otherwise
= forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ TcSolverReportMsg
safe_haskell_msg
where
orig :: CtOrigin
orig = ErrorItem -> CtOrigin
errorItemOrigin ErrorItem
item
pred :: Type
pred = ErrorItem -> Type
errorItemPred ErrorItem
item
(Class
clas, [Type]
tys) = HasDebugCallStack => Type -> (Class, [Type])
getClassPredTys Type
pred
ispecs :: [ClsInst]
ispecs = [ClsInst
ispec | (ClsInst
ispec, [Maybe Type]
_) <- [InstMatch]
matches]
unsafe_ispecs :: [ClsInst]
unsafe_ispecs = [ClsInst
ispec | (ClsInst
ispec, [Maybe Type]
_) <- [InstMatch]
unsafe_overlapped]
get_candidate_instances :: TcM [ClsInst]
get_candidate_instances :: TcM [ClsInst]
get_candidate_instances
| [Type
ty] <- [Type]
tys
= do { InstEnvs
instEnvs <- TcM InstEnvs
tcGetInstEnvs
; forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. (a -> Bool) -> [a] -> [a]
filter (Type -> ClsInst -> Bool
is_candidate_inst Type
ty)
(InstEnvs -> Class -> [ClsInst]
classInstances InstEnvs
instEnvs Class
clas)) }
| Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return []
is_candidate_inst :: Type -> ClsInst -> Bool
is_candidate_inst Type
ty ClsInst
inst
| [Type
other_ty] <- ClsInst -> [Type]
is_tys ClsInst
inst
, Just (TyCon
tc1, [Type]
_) <- HasCallStack => Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
ty
, Just (TyCon
tc2, [Type]
_) <- HasCallStack => Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
other_ty
= let n1 :: Name
n1 = TyCon -> Name
tyConName TyCon
tc1
n2 :: Name
n2 = TyCon -> Name
tyConName TyCon
tc2
different_names :: Bool
different_names = Name
n1 forall a. Eq a => a -> a -> Bool
/= Name
n2
same_occ_names :: Bool
same_occ_names = Name -> OccName
nameOccName Name
n1 forall a. Eq a => a -> a -> Bool
== Name -> OccName
nameOccName Name
n2
in Bool
different_names Bool -> Bool -> Bool
&& Bool
same_occ_names
| Bool
otherwise = Bool
False
record_field_suggestions :: TcM ([ImportError], [GhcHint])
record_field_suggestions :: TcM ([ImportError], [GhcHint])
record_field_suggestions = forall a b c. (a -> b -> c) -> b -> a -> c
flip (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return ([], [GhcHint]
noHints)) Maybe OccName
record_field forall a b. (a -> b) -> a -> b
$ \OccName
name ->
do { GlobalRdrEnv
glb_env <- TcRn GlobalRdrEnv
getGlobalRdrEnv
; LocalRdrEnv
lcl_env <- RnM LocalRdrEnv
getLocalRdrEnv
; if GlobalRdrEnv -> LocalRdrEnv -> OccName -> Bool
occ_name_in_scope GlobalRdrEnv
glb_env LocalRdrEnv
lcl_env OccName
name
then forall (m :: * -> *) a. Monad m => a -> m a
return ([], [GhcHint]
noHints)
else do { DynFlags
dflags <- forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
; ImportAvails
imp_info <- TcRn ImportAvails
getImports
; Module
curr_mod <- forall (m :: * -> *). HasModule m => m Module
getModule
; HomePackageTable
hpt <- forall gbl lcl. TcRnIf gbl lcl HomePackageTable
getHpt
; forall (m :: * -> *) a. Monad m => a -> m a
return (WhatLooking
-> DynFlags
-> HomePackageTable
-> Module
-> GlobalRdrEnv
-> LocalRdrEnv
-> ImportAvails
-> RdrName
-> ([ImportError], [GhcHint])
unknownNameSuggestions WhatLooking
WL_RecField DynFlags
dflags HomePackageTable
hpt Module
curr_mod
GlobalRdrEnv
glb_env LocalRdrEnv
emptyLocalRdrEnv ImportAvails
imp_info (OccName -> RdrName
mkRdrUnqual OccName
name)) } }
occ_name_in_scope :: GlobalRdrEnv -> LocalRdrEnv -> OccName -> Bool
occ_name_in_scope GlobalRdrEnv
glb_env LocalRdrEnv
lcl_env OccName
occ_name = Bool -> Bool
not forall a b. (a -> b) -> a -> b
$
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (GlobalRdrEnv -> OccName -> [GlobalRdrElt]
lookupGlobalRdrEnv GlobalRdrEnv
glb_env OccName
occ_name) Bool -> Bool -> Bool
&&
forall a. Maybe a -> Bool
isNothing (LocalRdrEnv -> OccName -> Maybe Name
lookupLocalRdrOcc LocalRdrEnv
lcl_env OccName
occ_name)
record_field :: Maybe OccName
record_field = case CtOrigin
orig of
HasFieldOrigin FastString
name -> forall a. a -> Maybe a
Just (FastString -> OccName
mkVarOccFS FastString
name)
CtOrigin
_ -> forall a. Maybe a
Nothing
cannot_resolve_msg :: ErrorItem -> [ClsInst] -> RelevantBindings
-> [ImportError] -> [GhcHint] -> TcSolverReportMsg
cannot_resolve_msg :: ErrorItem
-> [ClsInst]
-> RelevantBindings
-> [ImportError]
-> [GhcHint]
-> TcSolverReportMsg
cannot_resolve_msg ErrorItem
item [ClsInst]
candidate_insts RelevantBindings
binds [ImportError]
imp_errs [GhcHint]
field_suggestions
= ErrorItem
-> [ClsInst]
-> [ClsInst]
-> [ImportError]
-> [GhcHint]
-> RelevantBindings
-> TcSolverReportMsg
CannotResolveInstance ErrorItem
item (PotentialUnifiers -> [ClsInst]
getPotentialUnifiers PotentialUnifiers
unifiers) [ClsInst]
candidate_insts [ImportError]
imp_errs [GhcHint]
field_suggestions RelevantBindings
binds
overlap_msg, safe_haskell_msg :: TcSolverReportMsg
overlap_msg :: TcSolverReportMsg
overlap_msg
= forall a. HasCallStack => Bool -> a -> a
assert (Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [InstMatch]
matches)) forall a b. (a -> b) -> a -> b
$ ErrorItem -> [ClsInst] -> [ClsInst] -> TcSolverReportMsg
OverlappingInstances ErrorItem
item [ClsInst]
ispecs (PotentialUnifiers -> [ClsInst]
getPotentialUnifiers PotentialUnifiers
unifiers)
safe_haskell_msg :: TcSolverReportMsg
safe_haskell_msg
= forall a. HasCallStack => Bool -> a -> a
assert ([InstMatch]
matches forall a. [a] -> Int -> Bool
`lengthIs` Int
1 Bool -> Bool -> Bool
&& Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ClsInst]
unsafe_ispecs)) forall a b. (a -> b) -> a -> b
$
ErrorItem -> [ClsInst] -> [ClsInst] -> TcSolverReportMsg
UnsafeOverlap ErrorItem
item [ClsInst]
ispecs [ClsInst]
unsafe_ispecs
relevantBindings :: Bool
-> SolverReportErrCtxt -> ErrorItem
-> TcM (SolverReportErrCtxt, RelevantBindings, ErrorItem)
relevantBindings :: Bool
-> SolverReportErrCtxt
-> ErrorItem
-> TcM (SolverReportErrCtxt, RelevantBindings, ErrorItem)
relevantBindings Bool
want_filtering SolverReportErrCtxt
ctxt ErrorItem
item
= do { String -> SDoc -> TcM ()
traceTc String
"relevantBindings" (forall a. Outputable a => a -> SDoc
ppr ErrorItem
item)
; (TidyEnv
env1, CtOrigin
tidy_orig) <- TidyEnv -> CtOrigin -> TcM (TidyEnv, CtOrigin)
zonkTidyOrigin (SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt) (CtLoc -> CtOrigin
ctLocOrigin CtLoc
loc)
; let extra_tvs :: TyCoVarSet
extra_tvs = case CtOrigin
tidy_orig of
KindEqOrigin Type
t1 Type
t2 CtOrigin
_ Maybe TypeOrKind
_ -> [Type] -> TyCoVarSet
tyCoVarsOfTypes [Type
t1,Type
t2]
CtOrigin
_ -> TyCoVarSet
emptyVarSet
ct_fvs :: TyCoVarSet
ct_fvs = Type -> TyCoVarSet
tyCoVarsOfType (ErrorItem -> Type
errorItemPred ErrorItem
item) TyCoVarSet -> TyCoVarSet -> TyCoVarSet
`unionVarSet` TyCoVarSet
extra_tvs
loc' :: CtLoc
loc' = CtLoc -> CtOrigin -> CtLoc
setCtLocOrigin CtLoc
loc CtOrigin
tidy_orig
item' :: ErrorItem
item' = ErrorItem
item { ei_loc :: CtLoc
ei_loc = CtLoc
loc' }
; (TidyEnv
env2, NameEnv Type
lcl_name_cache) <- TidyEnv -> [TcLclEnv] -> TcM (TidyEnv, NameEnv Type)
zonkTidyTcLclEnvs TidyEnv
env1 [TcLclEnv
lcl_env]
; RelevantBindings
relev_bds <- Bool
-> TcLclEnv -> NameEnv Type -> TyCoVarSet -> TcM RelevantBindings
relevant_bindings Bool
want_filtering TcLclEnv
lcl_env NameEnv Type
lcl_name_cache TyCoVarSet
ct_fvs
; let ctxt' :: SolverReportErrCtxt
ctxt' = SolverReportErrCtxt
ctxt { cec_tidy :: TidyEnv
cec_tidy = TidyEnv
env2 }
; forall (m :: * -> *) a. Monad m => a -> m a
return (SolverReportErrCtxt
ctxt', RelevantBindings
relev_bds, ErrorItem
item') }
where
loc :: CtLoc
loc = ErrorItem -> CtLoc
errorItemCtLoc ErrorItem
item
lcl_env :: TcLclEnv
lcl_env = CtLoc -> TcLclEnv
ctLocEnv CtLoc
loc
relevant_bindings :: Bool
-> TcLclEnv
-> NameEnv Type
-> TyCoVarSet
-> TcM RelevantBindings
relevant_bindings :: Bool
-> TcLclEnv -> NameEnv Type -> TyCoVarSet -> TcM RelevantBindings
relevant_bindings Bool
want_filtering TcLclEnv
lcl_env NameEnv Type
lcl_name_env TyCoVarSet
ct_tvs
= do { DynFlags
dflags <- forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
; String -> SDoc -> TcM ()
traceTc String
"relevant_bindings" forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
vcat [ forall a. Outputable a => a -> SDoc
ppr TyCoVarSet
ct_tvs
, forall a. (a -> SDoc) -> [a] -> SDoc
pprWithCommas forall a. a -> a
id [ forall a. Outputable a => a -> SDoc
ppr TcId
id SDoc -> SDoc -> SDoc
<+> SDoc
dcolon SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr (TcId -> Type
idType TcId
id)
| TcIdBndr TcId
id TopLevelFlag
_ <- TcLclEnv -> TcBinderStack
tcl_bndrs TcLclEnv
lcl_env ]
, forall a. (a -> SDoc) -> [a] -> SDoc
pprWithCommas forall a. a -> a
id
[ forall a. Outputable a => a -> SDoc
ppr Name
id | TcIdBndr_ExpType Name
id ExpType
_ TopLevelFlag
_ <- TcLclEnv -> TcBinderStack
tcl_bndrs TcLclEnv
lcl_env ] ]
; DynFlags
-> Maybe Int
-> TyCoVarSet
-> RelevantBindings
-> TcBinderStack
-> TcM RelevantBindings
go DynFlags
dflags (DynFlags -> Maybe Int
maxRelevantBinds DynFlags
dflags)
TyCoVarSet
emptyVarSet ([(Name, Type)] -> Bool -> RelevantBindings
RelevantBindings [] Bool
False)
(forall a. HasOccName a => [a] -> [a]
removeBindingShadowing forall a b. (a -> b) -> a -> b
$ TcLclEnv -> TcBinderStack
tcl_bndrs TcLclEnv
lcl_env)
}
where
run_out :: Maybe Int -> Bool
run_out :: Maybe Int -> Bool
run_out Maybe Int
Nothing = Bool
False
run_out (Just Int
n) = Int
n forall a. Ord a => a -> a -> Bool
<= Int
0
dec_max :: Maybe Int -> Maybe Int
dec_max :: Maybe Int -> Maybe Int
dec_max = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int
n -> Int
n forall a. Num a => a -> a -> a
- Int
1)
go :: DynFlags -> Maybe Int -> TcTyVarSet
-> RelevantBindings
-> [TcBinder]
-> TcM RelevantBindings
go :: DynFlags
-> Maybe Int
-> TyCoVarSet
-> RelevantBindings
-> TcBinderStack
-> TcM RelevantBindings
go DynFlags
_ Maybe Int
_ TyCoVarSet
_ (RelevantBindings [(Name, Type)]
bds Bool
discards) []
= forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [(Name, Type)] -> Bool -> RelevantBindings
RelevantBindings (forall a. [a] -> [a]
reverse [(Name, Type)]
bds) Bool
discards
go DynFlags
dflags Maybe Int
n_left TyCoVarSet
tvs_seen rels :: RelevantBindings
rels@(RelevantBindings [(Name, Type)]
bds Bool
discards) (TcBinder
tc_bndr : TcBinderStack
tc_bndrs)
= case TcBinder
tc_bndr of
TcTvBndr {} -> TcM RelevantBindings
discard_it
TcIdBndr TcId
id TopLevelFlag
top_lvl -> Name -> TopLevelFlag -> TcM RelevantBindings
go2 (TcId -> Name
idName TcId
id) TopLevelFlag
top_lvl
TcIdBndr_ExpType Name
name ExpType
et TopLevelFlag
top_lvl ->
do { Maybe Type
mb_ty <- ExpType -> TcM (Maybe Type)
readExpType_maybe ExpType
et
; case Maybe Type
mb_ty of
Just Type
_ty -> Name -> TopLevelFlag -> TcM RelevantBindings
go2 Name
name TopLevelFlag
top_lvl
Maybe Type
Nothing -> TcM RelevantBindings
discard_it
}
where
discard_it :: TcM RelevantBindings
discard_it = DynFlags
-> Maybe Int
-> TyCoVarSet
-> RelevantBindings
-> TcBinderStack
-> TcM RelevantBindings
go DynFlags
dflags Maybe Int
n_left TyCoVarSet
tvs_seen RelevantBindings
rels TcBinderStack
tc_bndrs
go2 :: Name -> TopLevelFlag -> TcM RelevantBindings
go2 Name
id_name TopLevelFlag
top_lvl
= do { let tidy_ty :: Type
tidy_ty = case forall a. NameEnv a -> Name -> Maybe a
lookupNameEnv NameEnv Type
lcl_name_env Name
id_name of
Just Type
tty -> Type
tty
Maybe Type
Nothing -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"relevant_bindings" (forall a. Outputable a => a -> SDoc
ppr Name
id_name)
; String -> SDoc -> TcM ()
traceTc String
"relevantBindings 1" (forall a. Outputable a => a -> SDoc
ppr Name
id_name SDoc -> SDoc -> SDoc
<+> SDoc
dcolon SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Type
tidy_ty)
; let id_tvs :: TyCoVarSet
id_tvs = Type -> TyCoVarSet
tyCoVarsOfType Type
tidy_ty
bd :: (Name, Type)
bd = (Name
id_name, Type
tidy_ty)
new_seen :: TyCoVarSet
new_seen = TyCoVarSet
tvs_seen TyCoVarSet -> TyCoVarSet -> TyCoVarSet
`unionVarSet` TyCoVarSet
id_tvs
; if (Bool
want_filtering Bool -> Bool -> Bool
&& Bool -> Bool
not (DynFlags -> Bool
hasPprDebug DynFlags
dflags)
Bool -> Bool -> Bool
&& TyCoVarSet
id_tvs TyCoVarSet -> TyCoVarSet -> Bool
`disjointVarSet` TyCoVarSet
ct_tvs)
then TcM RelevantBindings
discard_it
else if TopLevelFlag -> Bool
isTopLevel TopLevelFlag
top_lvl Bool -> Bool -> Bool
&& Bool -> Bool
not (forall a. Maybe a -> Bool
isNothing Maybe Int
n_left)
then TcM RelevantBindings
discard_it
else if Maybe Int -> Bool
run_out Maybe Int
n_left Bool -> Bool -> Bool
&& TyCoVarSet
id_tvs TyCoVarSet -> TyCoVarSet -> Bool
`subVarSet` TyCoVarSet
tvs_seen
then DynFlags
-> Maybe Int
-> TyCoVarSet
-> RelevantBindings
-> TcBinderStack
-> TcM RelevantBindings
go DynFlags
dflags Maybe Int
n_left TyCoVarSet
tvs_seen ([(Name, Type)] -> Bool -> RelevantBindings
RelevantBindings [(Name, Type)]
bds Bool
True)
TcBinderStack
tc_bndrs
else DynFlags
-> Maybe Int
-> TyCoVarSet
-> RelevantBindings
-> TcBinderStack
-> TcM RelevantBindings
go DynFlags
dflags (Maybe Int -> Maybe Int
dec_max Maybe Int
n_left) TyCoVarSet
new_seen
([(Name, Type)] -> Bool -> RelevantBindings
RelevantBindings ((Name, Type)
bdforall a. a -> [a] -> [a]
:[(Name, Type)]
bds) Bool
discards) TcBinderStack
tc_bndrs }
warnDefaulting :: TcTyVar -> [Ct] -> Type -> TcM ()
warnDefaulting :: TcId -> [Ct] -> Type -> TcM ()
warnDefaulting TcId
_ [] Type
_
= forall a. String -> a
panic String
"warnDefaulting: empty Wanteds"
warnDefaulting TcId
the_tv wanteds :: [Ct]
wanteds@(Ct
ct:[Ct]
_) Type
default_ty
= do { Bool
warn_default <- forall gbl lcl. WarningFlag -> TcRnIf gbl lcl Bool
woptM WarningFlag
Opt_WarnTypeDefaults
; TidyEnv
env0 <- TcM TidyEnv
tcInitTidyEnv
; let filtered :: [Ct]
filtered = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. CtOrigin -> Bool
isWantedSuperclassOrigin forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ct -> CtOrigin
ctOrigin) [Ct]
wanteds
tidy_env :: TidyEnv
tidy_env = TidyEnv -> [TcId] -> TidyEnv
tidyFreeTyCoVars TidyEnv
env0 forall a b. (a -> b) -> a -> b
$
Cts -> [TcId]
tyCoVarsOfCtsList (forall a. [a] -> Bag a
listToBag [Ct]
filtered)
tidy_wanteds :: [Ct]
tidy_wanteds = forall a b. (a -> b) -> [a] -> [b]
map (TidyEnv -> Ct -> Ct
tidyCt TidyEnv
tidy_env) [Ct]
filtered
tidy_tv :: Maybe TcId
tidy_tv = forall a. VarEnv a -> TcId -> Maybe a
lookupVarEnv (forall a b. (a, b) -> b
snd TidyEnv
tidy_env) TcId
the_tv
diag :: TcRnMessage
diag = [Ct] -> Maybe TcId -> Type -> TcRnMessage
TcRnWarnDefaulting [Ct]
tidy_wanteds Maybe TcId
tidy_tv Type
default_ty
loc :: CtLoc
loc = Ct -> CtLoc
ctLoc Ct
ct
; forall a. CtLoc -> TcM a -> TcM a
setCtLocM CtLoc
loc forall a b. (a -> b) -> a -> b
$ Bool -> TcRnMessage -> TcM ()
diagnosticTc Bool
warn_default TcRnMessage
diag }
solverReportMsg_ExpectedActuals :: TcSolverReportMsg -> [(Type, Type)]
solverReportMsg_ExpectedActuals :: TcSolverReportMsg -> [(Type, Type)]
solverReportMsg_ExpectedActuals
= \case
TcReportWithInfo TcSolverReportMsg
msg NonEmpty TcSolverReportInfo
infos ->
TcSolverReportMsg -> [(Type, Type)]
solverReportMsg_ExpectedActuals TcSolverReportMsg
msg
forall a. [a] -> [a] -> [a]
++ (TcSolverReportInfo -> [(Type, Type)]
solverReportInfo_ExpectedActuals forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty TcSolverReportInfo
infos)
Mismatch { mismatch_ty1 :: TcSolverReportMsg -> Type
mismatch_ty1 = Type
exp, mismatch_ty2 :: TcSolverReportMsg -> Type
mismatch_ty2 = Type
act } ->
[(Type
exp, Type
act)]
KindMismatch { kmismatch_expected :: TcSolverReportMsg -> Type
kmismatch_expected = Type
exp, kmismatch_actual :: TcSolverReportMsg -> Type
kmismatch_actual = Type
act } ->
[(Type
exp, Type
act)]
TypeEqMismatch { teq_mismatch_expected :: TcSolverReportMsg -> Type
teq_mismatch_expected = Type
exp, teq_mismatch_actual :: TcSolverReportMsg -> Type
teq_mismatch_actual = Type
act } ->
[(Type
exp,Type
act)]
TcSolverReportMsg
_ -> []
solverReportInfo_ExpectedActuals :: TcSolverReportInfo -> [(Type, Type)]
solverReportInfo_ExpectedActuals :: TcSolverReportInfo -> [(Type, Type)]
solverReportInfo_ExpectedActuals
= \case
ExpectedActual { ea_expected :: TcSolverReportInfo -> Type
ea_expected = Type
exp, ea_actual :: TcSolverReportInfo -> Type
ea_actual = Type
act } ->
[(Type
exp, Type
act)]
ExpectedActualAfterTySynExpansion
{ ea_expanded_expected :: TcSolverReportInfo -> Type
ea_expanded_expected = Type
exp, ea_expanded_actual :: TcSolverReportInfo -> Type
ea_expanded_actual = Type
act } ->
[(Type
exp, Type
act)]
TcSolverReportInfo
_ -> []