{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ParallelListComp #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module GHC.Tc.Errors(
reportUnsolved, reportAllUnsolved, warnAllUnsolved,
warnDefaulting,
solverReportMsg_ExpectedActuals, mismatchMsg_ExpectedActuals
) where
import GHC.Prelude
import GHC.Driver.Env (hsc_units)
import GHC.Driver.DynFlags
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.Types.CtLoc
import GHC.Tc.Utils.TcMType
import GHC.Tc.Zonk.Type
import GHC.Tc.Utils.TcType
import GHC.Tc.Zonk.TcType
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
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.TyCo.Tidy ( tidyAvoiding )
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.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, union, sort, sortBy )
import Data.List.NonEmpty ( NonEmpty(..), nonEmpty )
import qualified Data.List.NonEmpty as NE
import Data.Ord ( comparing )
reportUnsolved :: WantedConstraints -> TcM (Bag EvBind)
reportUnsolved :: WantedConstraints -> TcM (Bag EvBind)
reportUnsolved WantedConstraints
wanted
= do { binds_var <- TcM EvBindsVar
newTcEvBinds
; defer_errors <- goptM Opt_DeferTypeErrors
; let type_errors | Bool -> Bool
not Bool
defer_errors = DiagnosticReason
ErrorWithoutFlag
| Bool
otherwise = WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnDeferredTypeErrors
; defer_holes <- goptM Opt_DeferTypedHoles
; let expr_holes | Bool -> Bool
not Bool
defer_holes = DiagnosticReason
ErrorWithoutFlag
| Bool
otherwise = WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnTypedHoles
; partial_sigs <- xoptM LangExt.PartialTypeSignatures
; let type_holes | Bool -> Bool
not Bool
partial_sigs
= DiagnosticReason
ErrorWithoutFlag
| Bool
otherwise
= WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnPartialTypeSignatures
; defer_out_of_scope <- goptM Opt_DeferOutOfScopeVariables
; let out_of_scope_holes | Bool -> Bool
not Bool
defer_out_of_scope
= DiagnosticReason
ErrorWithoutFlag
| Bool
otherwise
= WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnDeferredOutOfScopeVariables
; report_unsolved type_errors expr_holes
type_holes out_of_scope_holes
binds_var wanted
; ev_binds <- getTcEvBindsMap binds_var
; return (evBindMapBinds ev_binds)}
reportAllUnsolved :: WantedConstraints -> TcM ()
reportAllUnsolved :: WantedConstraints -> TcM ()
reportAllUnsolved WantedConstraints
wanted
= do { ev_binds <- TcM EvBindsVar
newNoTcEvBinds
; partial_sigs <- xoptM LangExt.PartialTypeSignatures
; let type_holes | Bool -> Bool
not Bool
partial_sigs = DiagnosticReason
ErrorWithoutFlag
| Bool
otherwise = WarningFlag -> DiagnosticReason
WarningWithFlag WarningFlag
Opt_WarnPartialTypeSignatures
; report_unsolved ErrorWithoutFlag
ErrorWithoutFlag type_holes ErrorWithoutFlag
ev_binds wanted }
warnAllUnsolved :: WantedConstraints -> TcM ()
warnAllUnsolved :: WantedConstraints -> TcM ()
warnAllUnsolved WantedConstraints
wanted
= do { ev_binds <- TcM EvBindsVar
newTcEvBinds
; report_unsolved WarningWithoutFlag
WarningWithoutFlag
WarningWithoutFlag
WarningWithoutFlag
ev_binds 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
= () -> TcM ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise
= do { String -> SDoc -> TcM ()
traceTc String
"reportUnsolved {" (SDoc -> TcM ()) -> SDoc -> TcM ()
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"type errors:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> DiagnosticReason -> SDoc
forall a. Outputable a => a -> SDoc
ppr DiagnosticReason
type_errors
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"expr holes:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> DiagnosticReason -> SDoc
forall a. Outputable a => a -> SDoc
ppr DiagnosticReason
expr_holes
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"type holes:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> DiagnosticReason -> SDoc
forall a. Outputable a => a -> SDoc
ppr DiagnosticReason
type_holes
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"scope holes:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> DiagnosticReason -> SDoc
forall a. Outputable a => a -> SDoc
ppr DiagnosticReason
out_of_scope_holes ]
; String -> SDoc -> TcM ()
traceTc String
"reportUnsolved (before zonking and tidying)" (WantedConstraints -> SDoc
forall a. Outputable a => a -> SDoc
ppr WantedConstraints
wanted)
; wanted <- ZonkM WantedConstraints -> TcM WantedConstraints
forall a. ZonkM a -> TcM a
liftZonkM (ZonkM WantedConstraints -> TcM WantedConstraints)
-> ZonkM WantedConstraints -> TcM WantedConstraints
forall a b. (a -> b) -> a -> b
$ WantedConstraints -> ZonkM WantedConstraints
zonkWC WantedConstraints
wanted
; let tidy_env = [OccName] -> (TidyEnv -> [TcId] -> TidyEnv) -> [TcId] -> TidyEnv
forall a. [OccName] -> (TidyEnv -> a -> TidyEnv) -> a -> TidyEnv
tidyAvoiding [OccName]
bound_occs TidyEnv -> [TcId] -> TidyEnv
tidyFreeTyCoVars [TcId]
free_tvs
free_tvs = (TcId -> Bool) -> [TcId] -> [TcId]
forall a. (a -> Bool) -> [a] -> [a]
filterOut TcId -> Bool
isCoVar ([TcId] -> [TcId]) -> [TcId] -> [TcId]
forall a b. (a -> b) -> a -> b
$
WantedConstraints -> [TcId]
tyCoVarsOfWCList WantedConstraints
wanted
bound_occs :: [OccName]
bound_occs = WantedConstraints -> [OccName]
boundOccNamesOfWC WantedConstraints
wanted
; traceTc "reportUnsolved (after zonking):" $
vcat [ text "Free tyvars:" <+> pprTyVars free_tvs
, text "Bound occs:" <+> ppr bound_occs
, text "Tidy env:" <+> ppr tidy_env
, text "Wanted:" <+> ppr wanted ]
; warn_redundant <- woptM Opt_WarnRedundantConstraints
; exp_syns <- goptM Opt_PrintExpandedSynonyms
; let 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 }
; tc_lvl <- getTcLevel
; reportWanteds err_ctxt tc_lvl wanted
; traceTc "reportUnsolved }" empty }
important :: SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important :: SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt TcSolverReportMsg
doc
= SolverReport { sr_important_msg :: SolverReportWithCtxt
sr_important_msg = SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt TcSolverReportMsg
doc
, sr_supplementary :: [SolverReportSupplementary]
sr_supplementary = [] }
add_relevant_bindings :: RelevantBindings -> SolverReport -> SolverReport
add_relevant_bindings :: RelevantBindings -> SolverReport -> SolverReport
add_relevant_bindings RelevantBindings
binds report :: SolverReport
report@(SolverReport { sr_supplementary :: SolverReport -> [SolverReportSupplementary]
sr_supplementary = [SolverReportSupplementary]
supp })
= SolverReport
report { sr_supplementary = SupplementaryBindings binds : supp }
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 = ErrorWithoutFlag
, cec_expr_holes = ErrorWithoutFlag
, cec_out_of_scope_holes = 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 -> CtLocEnv
ic_env = CtLocEnv
ct_loc_env
, ic_tclvl :: Implication -> TcLevel
ic_tclvl = TcLevel
tc_lvl })
| SkolemInfoAnon
BracketSkol <- SkolemInfoAnon
info
, Bool -> Bool
not Bool
insoluble
= () -> TcM ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise
= do { String -> SDoc -> TcM ()
traceTc String
"reportImplic" (SDoc -> TcM ()) -> SDoc -> TcM ()
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat
[ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"tidy env:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> TidyEnv -> SDoc
forall a. Outputable a => a -> SDoc
ppr (SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt)
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"skols: " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [TcId] -> SDoc
pprTyVars [TcId]
tvs
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"tidy skols:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [TcId] -> SDoc
pprTyVars [TcId]
tvs' ]
; Bool -> TcM () -> TcM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
bad_telescope (TcM () -> TcM ()) -> TcM () -> TcM ()
forall a b. (a -> b) -> a -> b
$ SolverReportErrCtxt
-> CtLocEnv -> SkolemInfoAnon -> [TcId] -> TcM ()
reportBadTelescope SolverReportErrCtxt
ctxt CtLocEnv
ct_loc_env SkolemInfoAnon
info [TcId]
tvs
; SolverReportErrCtxt -> TcLevel -> WantedConstraints -> TcM ()
reportWanteds SolverReportErrCtxt
ctxt' TcLevel
tc_lvl WantedConstraints
wanted
; SolverReportErrCtxt
-> CtLocEnv -> SkolemInfoAnon -> [TcId] -> TcM ()
warnRedundantConstraints SolverReportErrCtxt
ctxt' CtLocEnv
ct_loc_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) ([TcId] -> (TidyEnv, [TcId])) -> [TcId] -> (TidyEnv, [TcId])
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 = tvs'
, ic_given = map (tidyEvVar env1) given
, ic_info = info' }
ctxt1 :: SolverReportErrCtxt
ctxt1 = EvBindsVar -> SolverReportErrCtxt -> SolverReportErrCtxt
maybeSwitchOffDefer EvBindsVar
evb SolverReportErrCtxt
ctxt
ctxt' :: SolverReportErrCtxt
ctxt' = SolverReportErrCtxt
ctxt1 { cec_tidy = env1
, cec_encl = implic' : cec_encl ctxt
, cec_suppress = insoluble || cec_suppress ctxt
, cec_binds = 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 -> CtLocEnv -> SkolemInfoAnon -> [EvVar] -> TcM ()
warnRedundantConstraints :: SolverReportErrCtxt
-> CtLocEnv -> SkolemInfoAnon -> [TcId] -> TcM ()
warnRedundantConstraints SolverReportErrCtxt
ctxt CtLocEnv
env SkolemInfoAnon
info [TcId]
redundant_evs
| Bool -> Bool
not (SolverReportErrCtxt -> Bool
cec_warn_redundant SolverReportErrCtxt
ctxt)
= () -> TcM ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| [TcId] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TcId]
redundant_evs
= () -> TcM ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| InstSkol (IsQC {}) PatersonSize
_ <- SkolemInfoAnon
info
= () -> TcM ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| SigSkol UserTypeCtxt
user_ctxt Type
_ [(Name, TcId)]
_ <- SkolemInfoAnon
info
= Bool -> CtLocEnv -> TcM ()
report_redundant_msg Bool
True (CtLocEnv -> SrcSpan -> CtLocEnv
setCtLocEnvLoc CtLocEnv
env (UserTypeCtxt -> SrcSpan
redundantConstraintsSpan UserTypeCtxt
user_ctxt))
| Bool
otherwise
= Bool -> CtLocEnv -> TcM ()
report_redundant_msg Bool
False CtLocEnv
env
where
report_redundant_msg :: Bool
-> CtLocEnv
-> TcRn ()
report_redundant_msg :: Bool -> CtLocEnv -> TcM ()
report_redundant_msg Bool
show_info CtLocEnv
lcl_env
= do { msg <-
CtLocEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport
CtLocEnv
lcl_env
([TcId] -> (SkolemInfoAnon, Bool) -> TcRnMessage
TcRnRedundantConstraints [TcId]
redundant_evs (SkolemInfoAnon
info, Bool
show_info))
(SolverReportErrCtxt -> Maybe SolverReportErrCtxt
forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt)
[]
; reportDiagnostic msg }
reportBadTelescope :: SolverReportErrCtxt -> CtLocEnv -> SkolemInfoAnon -> [TcTyVar] -> TcM ()
reportBadTelescope :: SolverReportErrCtxt
-> CtLocEnv -> SkolemInfoAnon -> [TcId] -> TcM ()
reportBadTelescope SolverReportErrCtxt
ctxt CtLocEnv
env (ForAllSkol TyVarBndrs
telescope) [TcId]
skols
= do { msg <- CtLocEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport
CtLocEnv
env
(SolverReportWithCtxt -> DiagnosticReason -> TcRnMessage
TcRnSolverReport SolverReportWithCtxt
report DiagnosticReason
ErrorWithoutFlag)
(SolverReportErrCtxt -> Maybe SolverReportErrCtxt
forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt)
[]
; reportDiagnostic msg }
where
report :: SolverReportWithCtxt
report = SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt (TcSolverReportMsg -> SolverReportWithCtxt)
-> TcSolverReportMsg -> SolverReportWithCtxt
forall a b. (a -> b) -> a -> b
$ TyVarBndrs -> [TcId] -> TcSolverReportMsg
BadTelescope TyVarBndrs
telescope [TcId]
skols
reportBadTelescope SolverReportErrCtxt
_ CtLocEnv
_ SkolemInfoAnon
skol_info [TcId]
skols
= String -> SDoc -> TcM ()
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"reportBadTelescope" (SkolemInfoAnon -> SDoc
forall a. Outputable a => a -> SDoc
ppr SkolemInfoAnon
skol_info SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ [TcId] -> 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:" (Ct -> SDoc
forall a. Outputable a => a -> SDoc
ppr Ct
ct)
; Maybe ErrorItem -> TcM (Maybe ErrorItem)
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ErrorItem
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
; (suppress, m_evdest) <- case Ct -> CtEvidence
ctEvidence Ct
ct of
CtGiven {} -> (Bool, Maybe TcEvDest)
-> IOEnv (Env TcGblEnv TcLclEnv) (Bool, Maybe TcEvDest)
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
False, Maybe TcEvDest
forall a. Maybe a
Nothing)
CtWanted { ctev_rewriters :: CtEvidence -> RewriterSet
ctev_rewriters = RewriterSet
rewriters, ctev_dest :: CtEvidence -> TcEvDest
ctev_dest = TcEvDest
dest }
-> do { rewriters' <- RewriterSet -> TcM RewriterSet
zonkRewriterSet RewriterSet
rewriters
; return (not (isEmptyRewriterSet rewriters'), Just dest) }
; let m_reason = case Ct
ct of
CIrredCan (IrredCt { ir_reason :: IrredCt -> CtIrredReason
ir_reason = CtIrredReason
reason }) -> CtIrredReason -> Maybe CtIrredReason
forall a. a -> Maybe a
Just CtIrredReason
reason
Ct
_ -> Maybe CtIrredReason
forall a. Maybe a
Nothing
; return $ Just $ EI { ei_pred = ctPred ct
, ei_evdest = m_evdest
, ei_flavour = flav
, ei_loc = loc
, ei_m_reason = m_reason
, ei_suppress = suppress }}
unsuppressErrorItem :: ErrorItem -> ErrorItem
unsuppressErrorItem :: ErrorItem -> ErrorItem
unsuppressErrorItem ErrorItem
ei = ErrorItem
ei { ei_suppress = False }
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
forall doc. IsOutput doc => doc
empty
| Bool
otherwise
= do { tidy_items1 <- (Ct -> TcM (Maybe ErrorItem))
-> [Ct] -> IOEnv (Env TcGblEnv TcLclEnv) [ErrorItem]
forall (m :: * -> *) a b.
Applicative m =>
(a -> m (Maybe b)) -> [a] -> m [b]
mapMaybeM Ct -> TcM (Maybe ErrorItem)
mkErrorItem [Ct]
tidy_cts
; traceTc "reportWanteds 1" (vcat [ text "Simples =" <+> ppr simples
, text "Suppress =" <+> ppr (cec_suppress ctxt)
, text "tidy_cts =" <+> ppr tidy_cts
, text "tidy_items1 =" <+> ppr tidy_items1
, text "tidy_errs =" <+> ppr tidy_errs ])
; errs_already <- ifErrsM (return True) (return False)
; let tidy_items
| Bool -> Bool
not Bool
errs_already
, Bool -> Bool
not ((Ct -> Bool) -> Cts -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Ct -> Bool
ignoreConstraint Cts
simples)
, (ErrorItem -> Bool) -> [ErrorItem] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ErrorItem -> Bool
ei_suppress [ErrorItem]
tidy_items1
= (ErrorItem -> ErrorItem) -> [ErrorItem] -> [ErrorItem]
forall a b. (a -> b) -> [a] -> [b]
map ErrorItem -> ErrorItem
unsuppressErrorItem [ErrorItem]
tidy_items1
| Bool
otherwise
= [ErrorItem]
tidy_items1
; let (out_of_scope, other_holes, not_conc_errs, mult_co_errs) = partition_errors tidy_errs
ctxt_for_scope_errs = SolverReportErrCtxt
ctxt { cec_suppress = False }
; (_, no_out_of_scope) <- askNoErrs $
reportHoles tidy_items ctxt_for_scope_errs out_of_scope
; let ctxt_for_insols = SolverReportErrCtxt
ctxt { cec_suppress = not no_out_of_scope }
; reportHoles tidy_items ctxt_for_insols other_holes
; reportNotConcreteErrs ctxt_for_insols not_conc_errs
; when (null simples) $ reportMultiplicityCoercionErrs ctxt_for_insols mult_co_errs
; let (suppressed_items, items0) = partition suppress tidy_items
; traceTc "reportWanteds suppressed:" (ppr suppressed_items)
; (ctxt1, items1) <- tryReporters ctxt_for_insols report1 items0
; let ctxt2 = SolverReportErrCtxt
ctxt1 { cec_suppress = cec_suppress ctxt || cec_suppress ctxt1 }
; (ctxt3, leftovers) <- tryReporters ctxt2 report2 items1
; massertPpr (null leftovers)
(text "The following unsolved Wanted constraints \
\have not been reported to the user:"
$$ ppr leftovers)
; mapBagM_ (reportImplic ctxt2) implics
; whenNoErrs $
do { (_, more_leftovers) <- tryReporters ctxt3 report3 suppressed_items
; massertPpr (null more_leftovers) (ppr more_leftovers) } }
where
env :: TidyEnv
env = SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt
tidy_cts :: [Ct]
tidy_cts = Cts -> [Ct]
forall a. Bag a -> [a]
bagToList ((Ct -> Ct) -> Cts -> Cts
forall a b. (a -> b) -> Bag a -> Bag b
mapBag (TidyEnv -> Ct -> Ct
tidyCt TidyEnv
env) Cts
simples)
tidy_errs :: [DelayedError]
tidy_errs = Bag DelayedError -> [DelayedError]
forall a. Bag a -> [a]
bagToList ((DelayedError -> DelayedError)
-> Bag DelayedError -> Bag DelayedError
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], [(TcCoercion, CtLoc)])
partition_errors :: [DelayedError]
-> ([Hole], [Hole], [NotConcreteError], [(TcCoercionN, CtLoc)])
partition_errors []
= ([], [], [], [])
partition_errors (DelayedError
err:[DelayedError]
errs)
| ([Hole]
es1, [Hole]
es2, [NotConcreteError]
es3, [(TcCoercionN, CtLoc)]
es4) <- [DelayedError]
-> ([Hole], [Hole], [NotConcreteError], [(TcCoercionN, CtLoc)])
partition_errors [DelayedError]
errs
= case DelayedError
err of
DE_Hole Hole
hole
| Hole -> Bool
isOutOfScopeHole Hole
hole
-> (Hole
hole Hole -> [Hole] -> [Hole]
forall a. a -> [a] -> [a]
: [Hole]
es1, [Hole]
es2, [NotConcreteError]
es3, [(TcCoercionN, CtLoc)]
es4)
| Bool
otherwise
-> ([Hole]
es1, Hole
hole Hole -> [Hole] -> [Hole]
forall a. a -> [a] -> [a]
: [Hole]
es2, [NotConcreteError]
es3, [(TcCoercionN, CtLoc)]
es4)
DE_NotConcrete NotConcreteError
err
-> ([Hole]
es1, [Hole]
es2, NotConcreteError
err NotConcreteError -> [NotConcreteError] -> [NotConcreteError]
forall a. a -> [a] -> [a]
: [NotConcreteError]
es3, [(TcCoercionN, CtLoc)]
es4)
DE_Multiplicity TcCoercionN
mult_co CtLoc
loc
-> ([Hole]
es1, [Hole]
es2, [NotConcreteError]
es3, (TcCoercionN
mult_co, CtLoc
loc)(TcCoercionN, CtLoc)
-> [(TcCoercionN, CtLoc)] -> [(TcCoercionN, CtLoc)]
forall a. a -> [a] -> [a]
:[(TcCoercionN, CtLoc)]
es4)
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", ErrorItem -> Pred -> Bool
forall {p}. ErrorItem -> p -> Bool
is_user_type_error, Bool
True, Reporter
mkUserTypeErrorReporter)
, ReporterSpec
given_eq_spec
, (String
"insoluble2", ErrorItem -> Pred -> Bool
forall {p}. p -> Pred -> Bool
utterly_wrong, Bool
True, (SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> NonEmpty 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 -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
mkGroupReporter HasDebugCallStack =>
SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkFRRErr)
, (String
"skolem eq2", ErrorItem -> Pred -> Bool
skolem_eq, Bool
True, Reporter
mkSkolReporter)
, (String
"non-tv eq", ErrorItem -> Pred -> Bool
forall {p}. p -> Pred -> Bool
non_tv_eq, Bool
True, Reporter
mkSkolReporter)
, (String
"Homo eqs", ErrorItem -> Pred -> Bool
forall {p}. p -> Pred -> Bool
is_homo_equality, Bool
True, (SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkEqErr)
, (String
"Other eqs", ErrorItem -> Pred -> Bool
is_equality, Bool
True, (SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkEqErr)
]
report2 :: [ReporterSpec]
report2 = [ (String
"Implicit params", ErrorItem -> Pred -> Bool
is_ip, Bool
False, (SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkIPErr)
, (String
"Irreds", ErrorItem -> Pred -> Bool
is_irred, Bool
False, (SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkIrredErr)
, (String
"Dicts", ErrorItem -> Pred -> Bool
is_dict, Bool
False, (SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
mkGroupReporter HasDebugCallStack =>
SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkDictErr) ]
report3 :: [(String, ErrorItem -> p -> Bool, Bool, Reporter)]
report3 = [ (String
"wanted/wanted fundeps", ErrorItem -> p -> Bool
forall {p}. ErrorItem -> p -> Bool
is_ww_fundep, Bool
True, (SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> NonEmpty 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
_ = Maybe FixedRuntimeRepErrorInfo -> Bool
forall a. Maybe a -> Bool
isJust (Maybe FixedRuntimeRepErrorInfo -> Bool)
-> Maybe FixedRuntimeRepErrorInfo -> Bool
forall a b. (a -> b) -> a -> b
$ HasDebugCallStack => ErrorItem -> Maybe FixedRuntimeRepErrorInfo
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
containsUserTypeError (ErrorItem -> Type
errorItemPred ErrorItem
item)
is_homo_equality :: p -> Pred -> Bool
is_homo_equality p
_ (EqPred EqRel
_ Type
ty1 Type
ty2)
= HasDebugCallStack => Type -> Type
Type -> Type
typeKind Type
ty1 HasDebugCallStack => Type -> Type -> Bool
Type -> Type -> Bool
`tcEqType` HasDebugCallStack => Type -> Type
Type -> Type
typeKind 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 (CtOrigin -> Bool) -> (ErrorItem -> CtOrigin) -> ErrorItem -> Bool
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 HasGivenEqs -> HasGivenEqs -> Bool
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 HasDebugCallStack => Type -> Maybe (TyCon, [Type])
Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
ty of
Just (TyCon
tc,[Type]
_) | TyCon -> Bool
isTypeFamilyTyCon TyCon
tc -> TyCon -> Maybe TyCon
forall a. a -> Maybe a
Just TyCon
tc
Maybe (TyCon, [Type])
_ -> Maybe TyCon
forall a. Maybe a
Nothing
type Reporter
= SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM ()
type ReporterSpec
= ( String
, ErrorItem -> Pred -> Bool
, Bool
, Reporter)
mkSkolReporter :: Reporter
mkSkolReporter :: Reporter
mkSkolReporter SolverReportErrCtxt
ctxt NonEmpty ErrorItem
items
= (NonEmpty ErrorItem -> TcM ()) -> [NonEmpty ErrorItem] -> TcM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
reportGroup SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkEqErr SolverReportErrCtxt
ctxt) ([ErrorItem] -> [NonEmpty ErrorItem]
group (NonEmpty ErrorItem -> [ErrorItem]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty ErrorItem
items))
where
group :: [ErrorItem] -> [NonEmpty ErrorItem]
group [] = []
group (ErrorItem
item:[ErrorItem]
items) = (ErrorItem
item ErrorItem -> [ErrorItem] -> NonEmpty ErrorItem
forall a. a -> [a] -> NonEmpty a
:| [ErrorItem]
yeses) NonEmpty ErrorItem -> [NonEmpty ErrorItem] -> [NonEmpty ErrorItem]
forall a. a -> [a] -> [a]
: [ErrorItem] -> [NonEmpty ErrorItem]
group [ErrorItem]
noes
where
([ErrorItem]
yeses, [ErrorItem]
noes) = (ErrorItem -> Bool) -> [ErrorItem] -> ([ErrorItem], [ErrorItem])
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
diag_opts <- DynFlags -> DiagOpts
initDiagOpts (DynFlags -> DiagOpts)
-> IOEnv (Env TcGblEnv TcLclEnv) DynFlags
-> IOEnv (Env TcGblEnv TcLclEnv) DiagOpts
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IOEnv (Env TcGblEnv TcLclEnv) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
let severity = DiagOpts -> DiagnosticReason -> Severity
diagReasonSeverity DiagOpts
diag_opts (SolverReportErrCtxt -> DiagnosticReason
cec_type_holes SolverReportErrCtxt
ctxt)
holes' = (Hole -> Bool) -> [Hole] -> [Hole]
forall a. (a -> Bool) -> [a] -> [a]
filter (Severity -> Hole -> Bool
keepThisHole Severity
severity) [Hole]
holes
(tidy_env', lcl_name_cache) <- liftZonkM $
zonkTidyTcLclEnvs (cec_tidy ctxt) (map (ctl_env . hole_loc) holes')
let ctxt' = SolverReportErrCtxt
ctxt { cec_tidy = tidy_env' }
forM_ holes' $ \Hole
hole -> do { msg <- NameEnv Type
-> [ErrorItem]
-> SolverReportErrCtxt
-> Hole
-> TcM (MsgEnvelope TcRnMessage)
mkHoleError NameEnv Type
lcl_name_cache [ErrorItem]
tidy_items SolverReportErrCtxt
ctxt' Hole
hole
; reportDiagnostic 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 -> [CtLocEnv] -> ZonkM (TidyEnv, NameEnv Type)
zonkTidyTcLclEnvs :: TidyEnv -> [CtLocEnv] -> ZonkM (TidyEnv, NameEnv Type)
zonkTidyTcLclEnvs TidyEnv
tidy_env [CtLocEnv]
lcls = ((TidyEnv, NameEnv Type)
-> TcBinder -> ZonkM (TidyEnv, NameEnv Type))
-> (TidyEnv, NameEnv Type)
-> [TcBinder]
-> ZonkM (TidyEnv, NameEnv Type)
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (TidyEnv, NameEnv Type)
-> TcBinder -> ZonkM (TidyEnv, NameEnv Type)
go (TidyEnv
tidy_env, NameEnv Type
forall a. NameEnv a
emptyNameEnv) ((CtLocEnv -> [TcBinder]) -> [CtLocEnv] -> [TcBinder]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap CtLocEnv -> [TcBinder]
ctl_bndrs [CtLocEnv]
lcls)
where
go :: (TidyEnv, NameEnv Type)
-> TcBinder -> ZonkM (TidyEnv, NameEnv Type)
go (TidyEnv, NameEnv Type)
envs TcBinder
tc_bndr = case TcBinder
tc_bndr of
TcTvBndr {} -> (TidyEnv, NameEnv Type) -> ZonkM (TidyEnv, NameEnv Type)
forall a. a -> ZonkM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TidyEnv, NameEnv Type)
envs
TcIdBndr TcId
id TopLevelFlag
_top_lvl -> Name
-> Type -> (TidyEnv, NameEnv Type) -> ZonkM (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 { mb_ty <- IO (Maybe Type) -> ZonkM (Maybe Type)
forall a. IO a -> ZonkM a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Type) -> ZonkM (Maybe Type))
-> IO (Maybe Type) -> ZonkM (Maybe Type)
forall a b. (a -> b) -> a -> b
$ ExpType -> IO (Maybe Type)
forall (m :: * -> *). MonadIO m => ExpType -> m (Maybe Type)
readExpType_maybe ExpType
et
; case mb_ty of
Just Type
ty -> Name
-> Type -> (TidyEnv, NameEnv Type) -> ZonkM (TidyEnv, NameEnv Type)
go_one Name
name Type
ty (TidyEnv, NameEnv Type)
envs
Maybe Type
Nothing -> (TidyEnv, NameEnv Type) -> ZonkM (TidyEnv, NameEnv Type)
forall a. a -> ZonkM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TidyEnv, NameEnv Type)
envs
}
go_one :: Name
-> Type -> (TidyEnv, NameEnv Type) -> ZonkM (TidyEnv, NameEnv Type)
go_one Name
name Type
ty (TidyEnv
tidy_env, NameEnv Type
name_env) = do
if Name
name Name -> NameEnv Type -> Bool
forall a. Name -> NameEnv a -> Bool
`elemNameEnv` NameEnv Type
name_env
then (TidyEnv, NameEnv Type) -> ZonkM (TidyEnv, NameEnv Type)
forall a. a -> ZonkM a
forall (m :: * -> *) a. Monad m => a -> m a
return (TidyEnv
tidy_env, NameEnv Type
name_env)
else do
(tidy_env', tidy_ty) <- TidyEnv -> Type -> ZonkM (TidyEnv, Type)
zonkTidyTcType TidyEnv
tidy_env Type
ty
return (tidy_env', extendNameEnv name_env name tidy_ty)
reportNotConcreteErrs :: SolverReportErrCtxt -> [NotConcreteError] -> TcM ()
reportNotConcreteErrs :: SolverReportErrCtxt -> [NotConcreteError] -> TcM ()
reportNotConcreteErrs SolverReportErrCtxt
_ [] = () -> TcM ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
reportNotConcreteErrs SolverReportErrCtxt
ctxt errs :: [NotConcreteError]
errs@(NotConcreteError
err0:[NotConcreteError]
_)
= do { msg <- CtLocEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport (CtLoc -> CtLocEnv
ctLocEnv (NotConcreteError -> CtLoc
nce_loc NotConcreteError
err0)) TcRnMessage
diag (SolverReportErrCtxt -> Maybe SolverReportErrCtxt
forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt) []
; reportDiagnostic msg }
where
frr_origins :: [FixedRuntimeRepErrorInfo]
frr_origins = [NotConcreteError] -> [FixedRuntimeRepErrorInfo]
acc_errors [NotConcreteError]
errs
diag :: TcRnMessage
diag = SolverReportWithCtxt -> DiagnosticReason -> TcRnMessage
TcRnSolverReport
(SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt ([FixedRuntimeRepErrorInfo] -> TcSolverReportMsg
FixedRuntimeRepError [FixedRuntimeRepErrorInfo]
frr_origins))
DiagnosticReason
ErrorWithoutFlag
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 = Maybe (TcId, Type)
forall a. Maybe a
Nothing }
FixedRuntimeRepErrorInfo
-> [FixedRuntimeRepErrorInfo] -> [FixedRuntimeRepErrorInfo]
forall a. a -> [a] -> [a]
: [FixedRuntimeRepErrorInfo]
frr_errs
reportMultiplicityCoercionErrs :: SolverReportErrCtxt -> [(TcCoercion, CtLoc)] -> TcM ()
reportMultiplicityCoercionErrs :: SolverReportErrCtxt -> [(TcCoercionN, CtLoc)] -> TcM ()
reportMultiplicityCoercionErrs SolverReportErrCtxt
ctxt [(TcCoercionN, CtLoc)]
errs = ((TcCoercionN, CtLoc) -> TcM ())
-> [(TcCoercionN, CtLoc)] -> TcM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (TcCoercionN, CtLoc) -> TcM ()
reportOne [(TcCoercionN, CtLoc)]
errs
where
reportOne :: (TcCoercion, CtLoc) -> TcM ()
reportOne :: (TcCoercionN, CtLoc) -> TcM ()
reportOne (TcCoercionN
_co, CtLoc
loc)
= do { msg <- CtLocEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport (CtLoc -> CtLocEnv
ctLocEnv CtLoc
loc) TcRnMessage
diag (SolverReportErrCtxt -> Maybe SolverReportErrCtxt
forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt) []
; reportDiagnostic msg }
diag :: TcRnMessage
diag = SolverReportWithCtxt -> DiagnosticReason -> TcRnMessage
TcRnSolverReport
(SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt TcSolverReportMsg
MultiplicityCoercionsNotSupported)
DiagnosticReason
ErrorWithoutFlag
mkUserTypeErrorReporter :: Reporter
mkUserTypeErrorReporter :: Reporter
mkUserTypeErrorReporter SolverReportErrCtxt
ctxt
= (ErrorItem -> TcM ()) -> NonEmpty ErrorItem -> TcM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((ErrorItem -> TcM ()) -> NonEmpty ErrorItem -> TcM ())
-> (ErrorItem -> TcM ()) -> NonEmpty ErrorItem -> TcM ()
forall a b. (a -> b) -> a -> b
$ \ErrorItem
item -> do { let err :: SolverReport
err = SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt (TcSolverReportMsg -> SolverReport)
-> TcSolverReportMsg -> SolverReport
forall a b. (a -> b) -> a -> b
$ ErrorItem -> TcSolverReportMsg
mkUserTypeError ErrorItem
item
; SolverReportErrCtxt -> NonEmpty ErrorItem -> SolverReport -> TcM ()
maybeReportError SolverReportErrCtxt
ctxt (ErrorItem
item ErrorItem -> [ErrorItem] -> NonEmpty ErrorItem
forall a. a -> [a] -> NonEmpty a
:| []) SolverReport
err
; SolverReportErrCtxt -> SolverReport -> ErrorItem -> TcM ()
addDeferredBinding SolverReportErrCtxt
ctxt SolverReport
err ErrorItem
item }
mkUserTypeError :: ErrorItem -> TcSolverReportMsg
mkUserTypeError :: ErrorItem -> TcSolverReportMsg
mkUserTypeError ErrorItem
item
| Just Type
msg <- Type -> Maybe Type
getUserTypeErrorMsg Type
pty
= Type -> TcSolverReportMsg
UserTypeError Type
msg
| Just Type
msg <- Type -> Maybe Type
isUnsatisfiableCt_maybe Type
pty
= Type -> TcSolverReportMsg
UnsatisfiableError Type
msg
| Bool
otherwise
= String -> SDoc -> TcSolverReportMsg
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"mkUserTypeError" (ErrorItem -> SDoc
forall a. Outputable a => a -> SDoc
ppr ErrorItem
item)
where
pty :: Type
pty = ErrorItem -> Type
errorItemPred ErrorItem
item
mkGivenErrorReporter :: Reporter
mkGivenErrorReporter :: Reporter
mkGivenErrorReporter SolverReportErrCtxt
ctxt (ErrorItem
item:|[ErrorItem]
_)
= do { (ctxt, relevant_binds, item) <- Bool
-> SolverReportErrCtxt
-> ErrorItem
-> TcM (SolverReportErrCtxt, RelevantBindings, ErrorItem)
relevantBindings Bool
True SolverReportErrCtxt
ctxt ErrorItem
item
; let (implic:_) = cec_encl ctxt
loc' = CtLoc -> CtLocEnv -> CtLoc
setCtLocEnv (ErrorItem -> CtLoc
ei_loc ErrorItem
item) (Implication -> CtLocEnv
ic_env Implication
implic)
item' = ErrorItem
item { ei_loc = loc' }
; eq_err_msg <- mkEqErr_help ctxt item' ty1 ty2
; let supplementary = [ RelevantBindings -> SolverReportSupplementary
SupplementaryBindings RelevantBindings
relevant_binds ]
msg = Implication -> SolverReportWithCtxt -> TcRnMessage
TcRnInaccessibleCode Implication
implic (SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt TcSolverReportMsg
eq_err_msg)
; msg <- mkErrorReport (ctLocEnv loc') msg (Just ctxt) supplementary
; reportDiagnostic msg }
where
(Type
ty1, Type
ty2) = Type -> (Type, Type)
getEqPredTys (ErrorItem -> Type
errorItemPred ErrorItem
item)
ignoreErrorReporter :: Reporter
ignoreErrorReporter :: Reporter
ignoreErrorReporter SolverReportErrCtxt
ctxt NonEmpty ErrorItem
items
= do { String -> SDoc -> TcM ()
traceTc String
"mkGivenErrorReporter no" (NonEmpty ErrorItem -> SDoc
forall a. Outputable a => a -> SDoc
ppr NonEmpty ErrorItem
items SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ [Implication] -> SDoc
forall a. Outputable a => a -> SDoc
ppr (SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt))
; () -> TcM ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return () }
mkGroupReporter :: (SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
mkGroupReporter :: (SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
mkGroupReporter SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mk_err SolverReportErrCtxt
ctxt NonEmpty ErrorItem
items
= (NonEmpty ErrorItem -> TcM ()) -> [NonEmpty ErrorItem] -> TcM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
reportGroup SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mk_err SolverReportErrCtxt
ctxt) ((ErrorItem -> ErrorItem -> Ordering)
-> [ErrorItem] -> [NonEmpty ErrorItem]
forall a. (a -> a -> Ordering) -> [a] -> [NonEmpty a]
equivClasses ErrorItem -> ErrorItem -> Ordering
cmp_loc (NonEmpty ErrorItem -> [ErrorItem]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty 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 EqRel -> EqRel -> Bool
forall a. Eq a => a -> a -> Bool
== EqRel
eq_rel2) Bool -> Bool -> Bool
&& (Type
ty1 HasCallStack => Type -> Type -> Bool
Type -> Type -> Bool
`eqType` Type
ty2)
(Pred, Pred)
_ -> String -> SDoc -> Bool
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"mkSkolReporter" (ErrorItem -> SDoc
forall a. Outputable a => a -> SDoc
ppr ErrorItem
item1 SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ ErrorItem -> 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 RealSrcLoc -> RealSrcLoc -> Ordering
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 -> NonEmpty ErrorItem -> TcM SolverReport) -> Reporter
reportGroup :: (SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport)
-> Reporter
reportGroup SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mk_err SolverReportErrCtxt
ctxt NonEmpty ErrorItem
items
= do { err <- SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mk_err SolverReportErrCtxt
ctxt NonEmpty ErrorItem
items
; traceTc "About to maybeReportErr" $
vcat [ text "Constraint:" <+> ppr items
, text "cec_suppress =" <+> ppr (cec_suppress ctxt)
, text "cec_defer_type_errors =" <+> ppr (cec_defer_type_errors ctxt) ]
; maybeReportError ctxt items err
; traceTc "reportGroup" (ppr items)
; mapM_ (addDeferredBinding ctxt err) items }
nonDeferrableOrigin :: CtOrigin -> Bool
nonDeferrableOrigin :: CtOrigin -> Bool
nonDeferrableOrigin (NonLinearPatternOrigin {}) = Bool
True
nonDeferrableOrigin (OmittedFieldOrigin {}) = Bool
True
nonDeferrableOrigin (UsageEnvironmentOf {}) = Bool
True
nonDeferrableOrigin (FRROrigin {}) = Bool
True
nonDeferrableOrigin CtOrigin
_ = Bool
False
maybeReportError :: SolverReportErrCtxt
-> NonEmpty ErrorItem
-> SolverReport -> TcM ()
maybeReportError :: SolverReportErrCtxt -> NonEmpty ErrorItem -> SolverReport -> TcM ()
maybeReportError SolverReportErrCtxt
ctxt items :: NonEmpty ErrorItem
items@(ErrorItem
item1:|[ErrorItem]
_) (SolverReport { sr_important_msg :: SolverReport -> SolverReportWithCtxt
sr_important_msg = SolverReportWithCtxt
important
, sr_supplementary :: SolverReport -> [SolverReportSupplementary]
sr_supplementary = [SolverReportSupplementary]
supp })
= Bool -> TcM () -> TcM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (SolverReportErrCtxt -> Bool
cec_suppress SolverReportErrCtxt
ctxt
Bool -> Bool -> Bool
|| (ErrorItem -> Bool) -> NonEmpty ErrorItem -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ErrorItem -> Bool
ei_suppress NonEmpty ErrorItem
items) (TcM () -> TcM ()) -> TcM () -> TcM ()
forall a b. (a -> b) -> a -> b
$
do let reason :: DiagnosticReason
reason | (ErrorItem -> Bool) -> NonEmpty ErrorItem -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (CtOrigin -> Bool
nonDeferrableOrigin (CtOrigin -> Bool) -> (ErrorItem -> CtOrigin) -> ErrorItem -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorItem -> CtOrigin
errorItemOrigin) NonEmpty ErrorItem
items = DiagnosticReason
ErrorWithoutFlag
| Bool
otherwise = SolverReportErrCtxt -> DiagnosticReason
cec_defer_type_errors SolverReportErrCtxt
ctxt
diag :: TcRnMessage
diag = SolverReportWithCtxt -> DiagnosticReason -> TcRnMessage
TcRnSolverReport SolverReportWithCtxt
important DiagnosticReason
reason
msg <- CtLocEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport (CtLoc -> CtLocEnv
ctLocEnv (ErrorItem -> CtLoc
errorItemCtLoc ErrorItem
item1)) TcRnMessage
diag (SolverReportErrCtxt -> Maybe SolverReportErrCtxt
forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt) [SolverReportSupplementary]
supp
reportDiagnostic msg
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 { err_tm <- SolverReportErrCtxt -> CtLoc -> Type -> SolverReport -> TcM EvTerm
mkErrorTerm SolverReportErrCtxt
ctxt CtLoc
loc Type
item_ty SolverReport
err
; let ev_binds_var = SolverReportErrCtxt -> EvBindsVar
cec_binds SolverReportErrCtxt
ctxt
; case dest of
EvVarDest TcId
evar
-> EvBindsVar -> EvBind -> TcM ()
addTcEvBind EvBindsVar
ev_binds_var (EvBind -> TcM ()) -> EvBind -> TcM ()
forall a b. (a -> b) -> a -> b
$ TcId -> CanonicalEvidence -> EvTerm -> EvBind
mkWantedEvBind TcId
evar CanonicalEvidence
EvNonCanonical 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 (EvBind -> TcM ()) -> EvBind -> TcM ()
forall a b. (a -> b) -> a -> b
$ TcId -> CanonicalEvidence -> EvTerm -> EvBind
mkWantedEvBind TcId
co_var CanonicalEvidence
EvNonCanonical EvTerm
err_tm
; CoercionHole -> TcCoercionN -> TcM ()
fillCoercionHole CoercionHole
hole (TcId -> TcCoercionN
mkCoVarCo TcId
co_var) } }
addDeferredBinding SolverReportErrCtxt
_ SolverReport
_ ErrorItem
_ = () -> TcM ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
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_msg :: SolverReport -> SolverReportWithCtxt
sr_important_msg = SolverReportWithCtxt
important, sr_supplementary :: SolverReport -> [SolverReportSupplementary]
sr_supplementary = [SolverReportSupplementary]
supp })
= do { msg <- CtLocEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport
(CtLoc -> CtLocEnv
ctLocEnv CtLoc
ct_loc)
(SolverReportWithCtxt -> DiagnosticReason -> TcRnMessage
TcRnSolverReport SolverReportWithCtxt
important DiagnosticReason
ErrorWithoutFlag) (SolverReportErrCtxt -> Maybe SolverReportErrCtxt
forall a. a -> Maybe a
Just SolverReportErrCtxt
ctxt) [SolverReportSupplementary]
supp
; dflags <- getDynFlags
; let err_msg = DiagnosticOpts TcRnMessage -> MsgEnvelope TcRnMessage -> SDoc
forall e. Diagnostic e => DiagnosticOpts e -> MsgEnvelope e -> SDoc
pprLocMsgEnvelope (DynFlags -> DiagnosticOpts TcRnMessage
initTcMessageOpts DynFlags
dflags) MsgEnvelope TcRnMessage
msg
err_str = DynFlags -> SDoc -> String
showSDoc DynFlags
dflags (SDoc -> String) -> SDoc -> String
forall a b. (a -> b) -> a -> b
$
SDoc
err_msg SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"(deferred type error)"
; return $ evDelayedError ty 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)
= (ErrorItem -> Bool) -> [ErrorItem] -> ([ErrorItem], [ErrorItem])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (CtOrigin -> Bool
isVisibleOrigin (CtOrigin -> Bool) -> (ErrorItem -> CtOrigin) -> ErrorItem -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorItem -> CtOrigin
errorItemOrigin) [ErrorItem]
items
; String -> SDoc -> TcM ()
traceTc String
"tryReporters {" ([ErrorItem] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
vis_items SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ [ErrorItem] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [ErrorItem]
invis_items)
; (ctxt', items') <- SolverReportErrCtxt
-> [ReporterSpec]
-> [ErrorItem]
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
go SolverReportErrCtxt
ctxt [ReporterSpec]
reporters [ErrorItem]
vis_items [ErrorItem]
invis_items
; traceTc "tryReporters }" (ppr items')
; return (ctxt', items') }
where
go :: SolverReportErrCtxt
-> [ReporterSpec]
-> [ErrorItem]
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
go SolverReportErrCtxt
ctxt [] [ErrorItem]
vis_items [ErrorItem]
invis_items
= (SolverReportErrCtxt, [ErrorItem])
-> TcM (SolverReportErrCtxt, [ErrorItem])
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (SolverReportErrCtxt
ctxt, [ErrorItem]
vis_items [ErrorItem] -> [ErrorItem] -> [ErrorItem]
forall a. [a] -> [a] -> [a]
++ [ErrorItem]
invis_items)
go SolverReportErrCtxt
ctxt (ReporterSpec
r : [ReporterSpec]
rs) [ErrorItem]
vis_items [ErrorItem]
invis_items
= do { (ctxt', vis_items') <- SolverReportErrCtxt
-> ReporterSpec
-> [ErrorItem]
-> TcM (SolverReportErrCtxt, [ErrorItem])
tryReporter SolverReportErrCtxt
ctxt ReporterSpec
r [ErrorItem]
vis_items
; (ctxt'', invis_items') <- tryReporter ctxt' r invis_items
; go ctxt'' rs vis_items' 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 = case [ErrorItem] -> Maybe (NonEmpty ErrorItem)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty [ErrorItem]
yeses of
Maybe (NonEmpty ErrorItem)
Nothing -> (SolverReportErrCtxt, [ErrorItem])
-> TcM (SolverReportErrCtxt, [ErrorItem])
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SolverReportErrCtxt
ctxt, [ErrorItem]
items)
Just NonEmpty ErrorItem
yeses -> do
{ String -> SDoc -> TcM ()
traceTc String
"tryReporter{ " (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
str SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> NonEmpty ErrorItem -> SDoc
forall a. Outputable a => a -> SDoc
ppr NonEmpty ErrorItem
yeses)
; (_, no_errs) <- TcM () -> TcRn ((), Bool)
forall a. TcRn a -> TcRn (a, Bool)
askNoErrs (Reporter
reporter SolverReportErrCtxt
ctxt NonEmpty ErrorItem
yeses)
; let suppress_now = Bool -> Bool
not Bool
no_errs Bool -> Bool -> Bool
&& Bool
suppress_after
ctxt' = SolverReportErrCtxt
ctxt { cec_suppress = suppress_now || cec_suppress ctxt }
; traceTc "tryReporter end }" (text str <+> ppr (cec_suppress ctxt) <+> ppr suppress_after)
; return (ctxt', nos) }
where
([ErrorItem]
yeses, [ErrorItem]
nos) = (ErrorItem -> Bool) -> [ErrorItem] -> ([ErrorItem], [ErrorItem])
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 :: CtLocEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport :: CtLocEnv
-> TcRnMessage
-> Maybe SolverReportErrCtxt
-> [SolverReportSupplementary]
-> TcM (MsgEnvelope TcRnMessage)
mkErrorReport CtLocEnv
tcl_env TcRnMessage
msg Maybe SolverReportErrCtxt
mb_ctxt [SolverReportSupplementary]
supplementary
= do { mb_context <- (SolverReportErrCtxt -> IOEnv (Env TcGblEnv TcLclEnv) SDoc)
-> Maybe SolverReportErrCtxt
-> IOEnv (Env TcGblEnv TcLclEnv) (Maybe SDoc)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe b)
traverse (\ SolverReportErrCtxt
ctxt -> TidyEnv -> [ErrCtxt] -> IOEnv (Env TcGblEnv TcLclEnv) SDoc
mkErrInfo (SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt) (CtLocEnv -> [ErrCtxt]
ctl_ctxt CtLocEnv
tcl_env)) Maybe SolverReportErrCtxt
mb_ctxt
; unit_state <- hsc_units <$> getTopEnv
; hfdc <- getHoleFitDispConfig
; let
err_info =
SDoc -> SDoc -> ErrInfo
ErrInfo
(SDoc -> Maybe SDoc -> SDoc
forall a. a -> Maybe a -> a
fromMaybe SDoc
forall doc. IsOutput doc => doc
empty Maybe SDoc
mb_context)
([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ (SolverReportSupplementary -> SDoc)
-> [SolverReportSupplementary] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (HoleFitDispConfig -> SolverReportSupplementary -> SDoc
pprSolverReportSupplementary HoleFitDispConfig
hfdc) [SolverReportSupplementary]
supplementary)
; let detailed_msg = ErrInfo -> TcRnMessage -> TcRnMessageDetailed
mkDetailedMessage ErrInfo
err_info TcRnMessage
msg
; mkTcRnMessage
(RealSrcSpan (ctl_loc tcl_env) Strict.Nothing)
(TcRnMessageWithInfo unit_state $ detailed_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
forall doc. IsDoc doc => doc -> doc -> doc
$$ SDoc
refs_msg
where
fits_msg, refs_msg, fits_discard_msg, refs_discard_msg :: SDoc
fits_msg :: SDoc
fits_msg = Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppUnless ([HoleFit] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [HoleFit]
fits) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Valid hole fits include") Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ((HoleFit -> SDoc) -> [HoleFit] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (HoleFitDispConfig -> HoleFit -> SDoc
pprHoleFit HoleFitDispConfig
hfdc) [HoleFit]
fits)
SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppWhen Bool
discarded_fits SDoc
fits_discard_msg
refs_msg :: SDoc
refs_msg = Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppUnless ([HoleFit] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [HoleFit]
refs) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Valid refinement hole fits include") Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ((HoleFit -> SDoc) -> [HoleFit] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (HoleFitDispConfig -> HoleFit -> SDoc
pprHoleFit HoleFitDispConfig
hfdc) [HoleFit]
refs)
SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppWhen Bool
discarded_refs SDoc
refs_discard_msg
fits_discard_msg :: SDoc
fits_discard_msg =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"(Some hole fits suppressed;" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"use -fmax-valid-hole-fits=N" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"or -fno-max-valid-hole-fits)"
refs_discard_msg :: SDoc
refs_discard_msg =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"(Some refinement hole fits suppressed;" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"use -fmax-refinement-hole-fits=N" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"or -fno-max-refinement-hole-fits)"
pprConstraintsInclude :: [(PredType, RealSrcSpan)] -> SDoc
pprConstraintsInclude :: [(Type, RealSrcSpan)] -> SDoc
pprConstraintsInclude [(Type, RealSrcSpan)]
cts
= Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppUnless ([(Type, RealSrcSpan)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Type, RealSrcSpan)]
cts) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Constraints include")
Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ ((Type, RealSrcSpan) -> SDoc) -> [(Type, RealSrcSpan)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (Type, RealSrcSpan) -> SDoc
forall {a} {a}. (Outputable a, Outputable a) => (a, a) -> SDoc
pprConstraint [(Type, RealSrcSpan)]
cts)
where
pprConstraint :: (a, a) -> SDoc
pprConstraint (a
constraint, a
loc) =
a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
constraint SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"from" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
loc))
mkIrredErr :: SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkIrredErr :: SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkIrredErr SolverReportErrCtxt
ctxt NonEmpty ErrorItem
items
= do { (ctxt, binds, item1) <- Bool
-> SolverReportErrCtxt
-> ErrorItem
-> TcM (SolverReportErrCtxt, RelevantBindings, ErrorItem)
relevantBindings Bool
True SolverReportErrCtxt
ctxt ErrorItem
item1
; let msg = SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt (TcSolverReportMsg -> SolverReport)
-> TcSolverReportMsg -> SolverReport
forall a b. (a -> b) -> a -> b
$ MismatchMsg -> TcSolverReportMsg
mkPlainMismatchMsg (MismatchMsg -> TcSolverReportMsg)
-> MismatchMsg -> TcSolverReportMsg
forall a b. (a -> b) -> a -> b
$
[Implication]
-> NonEmpty ErrorItem -> Maybe CND_Extra -> MismatchMsg
CouldNotDeduce (SolverReportErrCtxt -> [Implication]
getUserGivens SolverReportErrCtxt
ctxt) (ErrorItem
item1 ErrorItem -> [ErrorItem] -> NonEmpty ErrorItem
forall a. a -> [a] -> NonEmpty a
:| [ErrorItem]
others) Maybe CND_Extra
forall a. Maybe a
Nothing
; return $ add_relevant_bindings binds msg }
where
ErrorItem
item1:|[ErrorItem]
others = (ErrorItem -> Bool) -> NonEmpty ErrorItem -> NonEmpty ErrorItem
forall a. (a -> Bool) -> NonEmpty a -> NonEmpty a
tryFilter (Bool -> Bool
not (Bool -> Bool) -> (ErrorItem -> Bool) -> ErrorItem -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorItem -> Bool
ei_suppress) NonEmpty ErrorItem
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 -> RdrName
hole_occ = RdrName
occ, hole_loc :: Hole -> CtLoc
hole_loc = CtLoc
ct_loc })
| Hole -> Bool
isOutOfScopeHole Hole
hole
= do { (imp_errs, hints)
<- LocalRdrEnv
-> WhatLooking -> RdrName -> RnM ([ImportError], [GhcHint])
unknownNameSuggestions (CtLocEnv -> LocalRdrEnv
ctl_rdr CtLocEnv
lcl_env) WhatLooking
WL_Anything RdrName
occ
; let
err = SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt
(TcSolverReportMsg -> SolverReportWithCtxt)
-> TcSolverReportMsg -> SolverReportWithCtxt
forall a b. (a -> b) -> a -> b
$ Hole -> HoleError -> TcSolverReportMsg
ReportHoleError Hole
hole
(HoleError -> TcSolverReportMsg) -> HoleError -> TcSolverReportMsg
forall a b. (a -> b) -> a -> b
$ [ImportError] -> [GhcHint] -> HoleError
OutOfScopeHole [ImportError]
imp_errs [GhcHint]
hints
report = SolverReportWithCtxt -> [SolverReportSupplementary] -> SolverReport
SolverReport SolverReportWithCtxt
err []
; maybeAddDeferredBindings ctxt hole report
; mkErrorReport lcl_env (TcRnSolverReport err (cec_out_of_scope_holes ctxt))
Nothing []
}
where
lcl_env :: CtLocEnv
lcl_env = CtLoc -> CtLocEnv
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 { rel_binds
<- Bool
-> CtLocEnv -> NameEnv Type -> TyCoVarSet -> TcM RelevantBindings
relevant_bindings Bool
False CtLocEnv
lcl_env NameEnv Type
lcl_name_cache (Type -> TyCoVarSet
tyCoVarsOfType Type
hole_ty)
; show_hole_constraints <- goptM Opt_ShowHoleConstraints
; let relevant_cts
| ExprHole HoleExprRef
_ <- HoleSort
sort, Bool
show_hole_constraints
= SolverReportErrCtxt -> [(Type, RealSrcSpan)]
givenConstraints SolverReportErrCtxt
ctxt
| Bool
otherwise
= []
; show_valid_hole_fits <- goptM Opt_ShowValidHoleFits
; (ctxt, hole_fits) <- if show_valid_hole_fits
then validHoleFits ctxt tidy_simples hole
else return (ctxt, noValidHoleFits)
; (grouped_skvs, other_tvs) <- liftZonkM $ zonkAndGroupSkolTvs hole_ty
; let reason | ExprHole HoleExprRef
_ <- HoleSort
sort = SolverReportErrCtxt -> DiagnosticReason
cec_expr_holes SolverReportErrCtxt
ctxt
| Bool
otherwise = SolverReportErrCtxt -> DiagnosticReason
cec_type_holes SolverReportErrCtxt
ctxt
err = SolverReportErrCtxt -> TcSolverReportMsg -> SolverReportWithCtxt
SolverReportWithCtxt SolverReportErrCtxt
ctxt
(TcSolverReportMsg -> SolverReportWithCtxt)
-> TcSolverReportMsg -> SolverReportWithCtxt
forall a b. (a -> b) -> a -> b
$ Hole -> HoleError -> TcSolverReportMsg
ReportHoleError Hole
hole
(HoleError -> TcSolverReportMsg) -> HoleError -> TcSolverReportMsg
forall a b. (a -> b) -> a -> b
$ HoleSort -> [TcId] -> [(SkolemInfoAnon, [TcId])] -> HoleError
HoleError HoleSort
sort [TcId]
other_tvs [(SkolemInfoAnon, [TcId])]
grouped_skvs
supp = [ RelevantBindings -> SolverReportSupplementary
SupplementaryBindings RelevantBindings
rel_binds
, [(Type, RealSrcSpan)] -> SolverReportSupplementary
SupplementaryCts [(Type, RealSrcSpan)]
relevant_cts
, ValidHoleFits -> SolverReportSupplementary
SupplementaryHoleFits ValidHoleFits
hole_fits ]
; maybeAddDeferredBindings ctxt hole (SolverReport err supp)
; mkErrorReport lcl_env (TcRnSolverReport err reason) (Just ctxt) supp
}
where
lcl_env :: CtLocEnv
lcl_env = CtLoc -> CtLocEnv
ctLocEnv CtLoc
ct_loc
zonkAndGroupSkolTvs :: Type -> ZonkM ([(SkolemInfoAnon, [TcTyVar])], [TcTyVar])
zonkAndGroupSkolTvs :: Type -> ZonkM ([(SkolemInfoAnon, [TcId])], [TcId])
zonkAndGroupSkolTvs Type
hole_ty = do
zonked_info <- ((SkolemInfo, [(TcId, Int)]) -> ZonkM (SkolemInfoAnon, [TcId]))
-> [(SkolemInfo, [(TcId, Int)])]
-> ZonkM [(SkolemInfoAnon, [TcId])]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (SkolemInfo, [(TcId, Int)]) -> ZonkM (SkolemInfoAnon, [TcId])
forall {f :: * -> *} {b} {b}.
Functor f =>
(SkolemInfo, f (b, b)) -> ZonkM (SkolemInfoAnon, f b)
zonk_skolem_info [(SkolemInfo, [(TcId, Int)])]
skolem_list
return (zonked_info, other_tvs)
where
zonk_skolem_info :: (SkolemInfo, f (b, b)) -> ZonkM (SkolemInfoAnon, f b)
zonk_skolem_info (SkolemInfo
sk, f (b, b)
tv) =
do { sk <- SkolemInfoAnon -> ZonkM SkolemInfoAnon
zonkSkolemInfoAnon (SkolemInfoAnon -> ZonkM SkolemInfoAnon)
-> SkolemInfoAnon -> ZonkM SkolemInfoAnon
forall a b. (a -> b) -> a -> b
$ SkolemInfo -> SkolemInfoAnon
getSkolemInfo SkolemInfo
sk
; return (sk, fst <$> tv) }
tvs :: [TcId]
tvs = Type -> [TcId]
tyCoVarsOfTypeList Type
hole_ty
([TcId]
skol_tvs, [TcId]
other_tvs) = (TcId -> Bool) -> [TcId] -> ([TcId], [TcId])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (TcId -> Bool
isTcTyVar (TcId -> Bool) -> (TcId -> Bool) -> TcId -> Bool
forall (f :: * -> *). Applicative f => f Bool -> f Bool -> f Bool
<&&> TcId -> Bool
isSkolemTyVar) [TcId]
tvs
group_skolems :: UM.UniqMap SkolemInfo ([(TcTyVar, Int)])
group_skolems :: UniqMap SkolemInfo [(TcId, Int)]
group_skolems = Bag (TcId, Int) -> [(TcId, Int)]
forall a. Bag a -> [a]
bagToList (Bag (TcId, Int) -> [(TcId, Int)])
-> UniqMap SkolemInfo (Bag (TcId, Int))
-> UniqMap SkolemInfo [(TcId, Int)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Bag (TcId, Int) -> Bag (TcId, Int) -> Bag (TcId, Int))
-> [(SkolemInfo, Bag (TcId, Int))]
-> UniqMap SkolemInfo (Bag (TcId, Int))
forall k a. Uniquable k => (a -> a -> a) -> [(k, a)] -> UniqMap k a
UM.listToUniqMap_C Bag (TcId, Int) -> Bag (TcId, Int) -> Bag (TcId, Int)
forall a. Bag a -> Bag a -> Bag a
unionBags
[(TcId -> SkolemInfo
skolemSkolInfo TcId
tv, (TcId, Int) -> Bag (TcId, Int)
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 = ((SkolemInfo, [(TcId, Int)])
-> (SkolemInfo, [(TcId, Int)]) -> Ordering)
-> [(SkolemInfo, [(TcId, Int)])] -> [(SkolemInfo, [(TcId, Int)])]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (((SkolemInfo, [(TcId, Int)]) -> [Int])
-> (SkolemInfo, [(TcId, Int)])
-> (SkolemInfo, [(TcId, Int)])
-> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing ([Int] -> [Int]
forall a. Ord a => [a] -> [a]
sort ([Int] -> [Int])
-> ((SkolemInfo, [(TcId, Int)]) -> [Int])
-> (SkolemInfo, [(TcId, Int)])
-> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((TcId, Int) -> Int) -> [(TcId, Int)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (TcId, Int) -> Int
forall a b. (a, b) -> b
snd ([(TcId, Int)] -> [Int])
-> ((SkolemInfo, [(TcId, Int)]) -> [(TcId, Int)])
-> (SkolemInfo, [(TcId, Int)])
-> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SkolemInfo, [(TcId, Int)]) -> [(TcId, Int)]
forall a b. (a, b) -> b
snd))
([(SkolemInfo, [(TcId, Int)])] -> [(SkolemInfo, [(TcId, Int)])])
-> [(SkolemInfo, [(TcId, Int)])] -> [(SkolemInfo, [(TcId, Int)])]
forall a b. (a -> b) -> a -> b
$ UniqMap SkolemInfo [(TcId, Int)] -> [(SkolemInfo, [(TcId, Int)])]
forall k a. UniqMap k a -> [(k, a)]
UM.nonDetUniqMapToList 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
Bool -> TcM () -> TcM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (SolverReportErrCtxt -> Bool
deferringAnyBindings SolverReportErrCtxt
ctxt) (TcM () -> TcM ()) -> TcM () -> TcM ()
forall a b. (a -> b) -> a -> b
$ do
err_tm <- SolverReportErrCtxt -> CtLoc -> Type -> SolverReport -> TcM EvTerm
mkErrorTerm SolverReportErrCtxt
ctxt (Hole -> CtLoc
hole_loc Hole
hole) Type
ref_ty SolverReport
report
writeMutVar ref err_tm
HoleSort
_ -> () -> TcM ()
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
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 { (tidy_env, fits) <- TidyEnv
-> [Implication]
-> [CtEvidence]
-> Hole
-> TcM (TidyEnv, ValidHoleFits)
findValidHoleFits TidyEnv
lcl_env [Implication]
implics ((ErrorItem -> Maybe CtEvidence) -> [ErrorItem] -> [CtEvidence]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ErrorItem -> Maybe CtEvidence
mk_wanted [ErrorItem]
simps) Hole
hole
; return (ctxt {cec_tidy = tidy_env}, fits) }
where
mk_wanted :: ErrorItem -> Maybe CtEvidence
mk_wanted :: ErrorItem -> Maybe CtEvidence
mk_wanted (EI { ei_pred :: ErrorItem -> Type
ei_pred = Type
pred, ei_evdest :: ErrorItem -> Maybe TcEvDest
ei_evdest = Maybe TcEvDest
m_dest, ei_loc :: ErrorItem -> CtLoc
ei_loc = CtLoc
loc })
| Just TcEvDest
dest <- Maybe TcEvDest
m_dest
= CtEvidence -> Maybe CtEvidence
forall a. a -> Maybe a
Just (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 })
| Bool
otherwise
= Maybe CtEvidence
forall a. Maybe a
Nothing
givenConstraints :: SolverReportErrCtxt -> [(Type, RealSrcSpan)]
givenConstraints :: SolverReportErrCtxt -> [(Type, RealSrcSpan)]
givenConstraints SolverReportErrCtxt
ctxt
= do { implic@Implic{ ic_given = given } <- SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt
; constraint <- given
; return (varType constraint, getCtLocEnvLoc (ic_env implic)) }
mkIPErr :: SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkIPErr :: SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkIPErr SolverReportErrCtxt
ctxt (ErrorItem
item1:|[ErrorItem]
others)
= do { (ctxt, binds, item1) <- Bool
-> SolverReportErrCtxt
-> ErrorItem
-> TcM (SolverReportErrCtxt, RelevantBindings, ErrorItem)
relevantBindings Bool
True SolverReportErrCtxt
ctxt ErrorItem
item1
; let msg = SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt (TcSolverReportMsg -> SolverReport)
-> TcSolverReportMsg -> SolverReport
forall a b. (a -> b) -> a -> b
$ NonEmpty ErrorItem -> TcSolverReportMsg
UnboundImplicitParams (ErrorItem
item1 ErrorItem -> [ErrorItem] -> NonEmpty ErrorItem
forall a. a -> [a] -> NonEmpty a
:| [ErrorItem]
others)
; return $ add_relevant_bindings binds msg }
mkFRRErr :: HasDebugCallStack => SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkFRRErr :: HasDebugCallStack =>
SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkFRRErr SolverReportErrCtxt
ctxt NonEmpty ErrorItem
items
= do {
; (_tidy_env, frr_infos) <-
ZonkM (TidyEnv, [FixedRuntimeRepErrorInfo])
-> TcM (TidyEnv, [FixedRuntimeRepErrorInfo])
forall a. ZonkM a -> TcM a
liftZonkM (ZonkM (TidyEnv, [FixedRuntimeRepErrorInfo])
-> TcM (TidyEnv, [FixedRuntimeRepErrorInfo]))
-> ZonkM (TidyEnv, [FixedRuntimeRepErrorInfo])
-> TcM (TidyEnv, [FixedRuntimeRepErrorInfo])
forall a b. (a -> b) -> a -> b
$ TidyEnv
-> [FixedRuntimeRepErrorInfo]
-> ZonkM (TidyEnv, [FixedRuntimeRepErrorInfo])
zonkTidyFRRInfos (SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt) ([FixedRuntimeRepErrorInfo]
-> ZonkM (TidyEnv, [FixedRuntimeRepErrorInfo]))
-> [FixedRuntimeRepErrorInfo]
-> ZonkM (TidyEnv, [FixedRuntimeRepErrorInfo])
forall a b. (a -> b) -> a -> b
$
(FixedRuntimeRepErrorInfo -> FixedRuntimeRepErrorInfo -> Ordering)
-> [FixedRuntimeRepErrorInfo] -> [FixedRuntimeRepErrorInfo]
forall a. (a -> a -> Ordering) -> [a] -> [a]
nubOrdBy (Type -> Type -> Ordering
nonDetCmpType (Type -> Type -> Ordering)
-> (FixedRuntimeRepErrorInfo -> Type)
-> FixedRuntimeRepErrorInfo
-> FixedRuntimeRepErrorInfo
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (FixedRuntimeRepOrigin -> Type
frr_type (FixedRuntimeRepOrigin -> Type)
-> (FixedRuntimeRepErrorInfo -> FixedRuntimeRepOrigin)
-> FixedRuntimeRepErrorInfo
-> Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FixedRuntimeRepErrorInfo -> FixedRuntimeRepOrigin
frr_info_origin)) ([FixedRuntimeRepErrorInfo] -> [FixedRuntimeRepErrorInfo])
-> [FixedRuntimeRepErrorInfo] -> [FixedRuntimeRepErrorInfo]
forall a b. (a -> b) -> a -> b
$
(ErrorItem -> FixedRuntimeRepErrorInfo)
-> [ErrorItem] -> [FixedRuntimeRepErrorInfo]
forall a b. (a -> b) -> [a] -> [b]
map (String
-> Maybe FixedRuntimeRepErrorInfo -> FixedRuntimeRepErrorInfo
forall a. HasDebugCallStack => String -> Maybe a -> a
expectJust String
"mkFRRErr" (Maybe FixedRuntimeRepErrorInfo -> FixedRuntimeRepErrorInfo)
-> (ErrorItem -> Maybe FixedRuntimeRepErrorInfo)
-> ErrorItem
-> FixedRuntimeRepErrorInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasDebugCallStack => ErrorItem -> Maybe FixedRuntimeRepErrorInfo
ErrorItem -> Maybe FixedRuntimeRepErrorInfo
fixedRuntimeRepOrigin_maybe) ([ErrorItem] -> [FixedRuntimeRepErrorInfo])
-> [ErrorItem] -> [FixedRuntimeRepErrorInfo]
forall a b. (a -> b) -> a -> b
$
NonEmpty ErrorItem -> [ErrorItem]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty ErrorItem
items
; return $ important ctxt $ FixedRuntimeRepError 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
= FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo
forall a. a -> Maybe a
Just (FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo)
-> FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo
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 = Maybe (TcId, Type)
forall a. Maybe a
Nothing }
| EqPred EqRel
NomEq Type
ty1 Type
ty2 <- Type -> Pred
classifyPredType (ErrorItem -> Type
errorItemPred ErrorItem
item)
= if | Just (TcId
tv1, ConcreteFRR FixedRuntimeRepOrigin
frr1) <- Type -> Maybe (TcId, ConcreteTvOrigin)
isConcreteTyVarTy_maybe Type
ty1
-> FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo
forall a. a -> Maybe a
Just (FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo)
-> FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo
forall a b. (a -> b) -> a -> b
$ FixedRuntimeRepOrigin
-> Maybe (TcId, Type) -> FixedRuntimeRepErrorInfo
FRR_Info FixedRuntimeRepOrigin
frr1 ((TcId, Type) -> Maybe (TcId, Type)
forall a. a -> Maybe a
Just (TcId
tv1, Type
ty2))
| Just (TcId
tv2, ConcreteFRR FixedRuntimeRepOrigin
frr2) <- Type -> Maybe (TcId, ConcreteTvOrigin)
isConcreteTyVarTy_maybe Type
ty2
-> FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo
forall a. a -> Maybe a
Just (FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo)
-> FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo
forall a b. (a -> b) -> a -> b
$ FixedRuntimeRepOrigin
-> Maybe (TcId, Type) -> FixedRuntimeRepErrorInfo
FRR_Info FixedRuntimeRepOrigin
frr2 ((TcId, Type) -> Maybe (TcId, Type)
forall a. a -> Maybe a
Just (TcId
tv2, Type
ty1))
| Bool
otherwise
-> Maybe FixedRuntimeRepErrorInfo
forall a. Maybe a
Nothing
| Bool
otherwise
= Maybe FixedRuntimeRepErrorInfo
forall a. Maybe a
Nothing
mkEqErr :: SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkEqErr :: SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkEqErr SolverReportErrCtxt
ctxt NonEmpty ErrorItem
items
| ErrorItem
item1 :| [ErrorItem]
_ <- (ErrorItem -> Bool) -> NonEmpty ErrorItem -> NonEmpty ErrorItem
forall a. (a -> Bool) -> NonEmpty a -> NonEmpty a
tryFilter (Bool -> Bool
not (Bool -> Bool) -> (ErrorItem -> Bool) -> ErrorItem -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorItem -> Bool
ei_suppress) NonEmpty ErrorItem
items
= SolverReportErrCtxt -> ErrorItem -> TcM SolverReport
mkEqErr1 SolverReportErrCtxt
ctxt ErrorItem
item1
mkEqErr1 :: SolverReportErrCtxt -> ErrorItem -> TcM SolverReport
mkEqErr1 :: SolverReportErrCtxt -> ErrorItem -> TcM SolverReport
mkEqErr1 SolverReportErrCtxt
ctxt ErrorItem
item
= do { (ctxt, binds, item) <- Bool
-> SolverReportErrCtxt
-> ErrorItem
-> TcM (SolverReportErrCtxt, RelevantBindings, ErrorItem)
relevantBindings Bool
True SolverReportErrCtxt
ctxt ErrorItem
item
; traceTc "mkEqErr1" (ppr item $$ pprCtOrigin (errorItemOrigin item))
; err_msg <- mkEqErr_help ctxt item ty1 ty2
; let
report = RelevantBindings -> SolverReport -> SolverReport
add_relevant_bindings RelevantBindings
binds
(SolverReport -> SolverReport) -> SolverReport -> SolverReport
forall a b. (a -> b) -> a -> b
$ SolverReportErrCtxt -> TcSolverReportMsg -> SolverReport
important SolverReportErrCtxt
ctxt TcSolverReportMsg
err_msg
; return 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) <- HasDebugCallStack => Type -> Maybe (TyCon, [Type])
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
= CoercibleMsg -> Maybe CoercibleMsg
forall a. a -> Maybe a
Just CoercibleMsg
msg
| Just (TyCon
tc, [Type]
tys) <- HasDebugCallStack => Type -> Maybe (TyCon, [Type])
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
= CoercibleMsg -> Maybe CoercibleMsg
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 HasCallStack => Type -> Type -> Bool
Type -> Type -> Bool
`eqType` Type
s2
, Type -> Bool
has_unknown_roles Type
s1
= CoercibleMsg -> Maybe CoercibleMsg
forall a. a -> Maybe a
Just (CoercibleMsg -> Maybe CoercibleMsg)
-> CoercibleMsg -> Maybe CoercibleMsg
forall a b. (a -> b) -> a -> b
$ Type -> CoercibleMsg
UnknownRoles Type
s1
| Bool
otherwise
= Maybe CoercibleMsg
forall a. Maybe a
Nothing
where
coercible_msg_for_tycon :: TyCon -> Maybe CoercibleMsg
coercible_msg_for_tycon TyCon
tc
| TyCon -> Bool
isAbstractTyCon TyCon
tc
= CoercibleMsg -> Maybe CoercibleMsg
forall a. a -> Maybe a
Just (CoercibleMsg -> Maybe CoercibleMsg)
-> CoercibleMsg -> Maybe CoercibleMsg
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
, Maybe (GlobalRdrEltX GREInfo) -> Bool
forall a. Maybe a -> Bool
isNothing (GlobalRdrEnv -> Name -> Maybe (GlobalRdrEltX GREInfo)
forall info.
Outputable info =>
GlobalRdrEnvX info -> Name -> Maybe (GlobalRdrEltX info)
lookupGRE_Name GlobalRdrEnv
rdr_env Name
dc_name)
= CoercibleMsg -> Maybe CoercibleMsg
forall a. a -> Maybe a
Just (CoercibleMsg -> Maybe CoercibleMsg)
-> CoercibleMsg -> Maybe CoercibleMsg
forall a b. (a -> b) -> a -> b
$ TyCon -> DataCon -> CoercibleMsg
OutOfScopeNewtypeConstructor TyCon
tc DataCon
data_con
| Bool
otherwise = Maybe CoercibleMsg
forall a. Maybe a
Nothing
has_unknown_roles :: Type -> Bool
has_unknown_roles Type
ty
| Just (TyCon
tc, [Type]
tys) <- HasDebugCallStack => Type -> Maybe (TyCon, [Type])
Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
ty
= [Type]
tys [Type] -> Int -> Bool
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
mkEqErr_help :: SolverReportErrCtxt
-> ErrorItem
-> TcType -> TcType -> TcM TcSolverReportMsg
mkEqErr_help :: SolverReportErrCtxt
-> ErrorItem -> Type -> Type -> TcM TcSolverReportMsg
mkEqErr_help SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2
| Just (TcId, TcCoercionN)
casted_tv1 <- Type -> Maybe (TcId, TcCoercionN)
getCastedTyVar_maybe Type
ty1
= SolverReportErrCtxt
-> ErrorItem
-> (TcId, TcCoercionN)
-> Type
-> TcM TcSolverReportMsg
mkTyVarEqErr SolverReportErrCtxt
ctxt ErrorItem
item (TcId, TcCoercionN)
casted_tv1 Type
ty2
| Just (TcId, TcCoercionN)
casted_tv2 <- Type -> Maybe (TcId, TcCoercionN)
getCastedTyVar_maybe Type
ty2
= SolverReportErrCtxt
-> ErrorItem
-> (TcId, TcCoercionN)
-> Type
-> TcM TcSolverReportMsg
mkTyVarEqErr SolverReportErrCtxt
ctxt ErrorItem
item (TcId, TcCoercionN)
casted_tv2 Type
ty1
| Bool
otherwise
= SolverReportErrCtxt
-> ErrorItem -> Type -> Type -> TcM TcSolverReportMsg
reportEqErr SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2
reportEqErr :: SolverReportErrCtxt
-> ErrorItem
-> TcType -> TcType
-> TcM TcSolverReportMsg
reportEqErr :: SolverReportErrCtxt
-> ErrorItem -> Type -> Type -> TcM TcSolverReportMsg
reportEqErr SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2
= do
mb_coercible_info <- if ErrorItem -> EqRel
errorItemEqRel ErrorItem
item EqRel -> EqRel -> Bool
forall a. Eq a => a -> a -> Bool
== EqRel
ReprEq
then Type -> Type -> TcM (Maybe CoercibleMsg)
coercible_msg Type
ty1 Type
ty2
else Maybe CoercibleMsg -> TcM (Maybe CoercibleMsg)
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CoercibleMsg
forall a. Maybe a
Nothing
tv_info <- case getTyVar_maybe ty2 of
Maybe TcId
Nothing -> Maybe TyVarInfo -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe TyVarInfo)
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TyVarInfo
forall a. Maybe a
Nothing
Just TcId
tv2 -> TyVarInfo -> Maybe TyVarInfo
forall a. a -> Maybe a
Just (TyVarInfo -> Maybe TyVarInfo)
-> IOEnv (Env TcGblEnv TcLclEnv) TyVarInfo
-> IOEnv (Env TcGblEnv TcLclEnv) (Maybe TyVarInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TcId, Maybe Implication)
-> Type -> IOEnv (Env TcGblEnv TcLclEnv) TyVarInfo
extraTyVarEqInfo (TcId
tv2, Maybe Implication
forall a. Maybe a
Nothing) Type
ty1
return $ Mismatch { mismatchMsg = mismatch
, mismatchTyVarInfo = tv_info
, mismatchAmbiguityInfo = eqInfos
, mismatchCoercibleInfo = mb_coercible_info }
where
mismatch :: MismatchMsg
mismatch = SolverReportErrCtxt -> ErrorItem -> Type -> Type -> MismatchMsg
misMatchOrCND SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2
eqInfos :: [AmbiguityInfo]
eqInfos = Type -> Type -> [AmbiguityInfo]
eqInfoMsgs Type
ty1 Type
ty2
coercible_msg :: TcType -> TcType -> TcM (Maybe CoercibleMsg)
coercible_msg :: Type -> Type -> TcM (Maybe CoercibleMsg)
coercible_msg Type
ty1 Type
ty2
= do
rdr_env <- TcRn GlobalRdrEnv
getGlobalRdrEnv
fam_envs <- tcGetFamInstEnvs
return $ mkCoercibleExplanation rdr_env fam_envs ty1 ty2
mkTyVarEqErr :: SolverReportErrCtxt -> ErrorItem
-> (TcTyVar, TcCoercionN) -> TcType -> TcM TcSolverReportMsg
mkTyVarEqErr :: SolverReportErrCtxt
-> ErrorItem
-> (TcId, TcCoercionN)
-> Type
-> TcM TcSolverReportMsg
mkTyVarEqErr SolverReportErrCtxt
ctxt ErrorItem
item (TcId, TcCoercionN)
casted_tv1 Type
ty2
= do { String -> SDoc -> TcM ()
traceTc String
"mkTyVarEqErr" (ErrorItem -> SDoc
forall a. Outputable a => a -> SDoc
ppr ErrorItem
item SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ (TcId, TcCoercionN) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (TcId, TcCoercionN)
casted_tv1 SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ Type -> SDoc
forall a. Outputable a => a -> SDoc
ppr Type
ty2)
; SolverReportErrCtxt
-> ErrorItem
-> (TcId, TcCoercionN)
-> Type
-> TcM TcSolverReportMsg
mkTyVarEqErr' SolverReportErrCtxt
ctxt ErrorItem
item (TcId, TcCoercionN)
casted_tv1 Type
ty2 }
mkTyVarEqErr' :: SolverReportErrCtxt -> ErrorItem
-> (TcTyVar, TcCoercionN) -> TcType -> TcM TcSolverReportMsg
mkTyVarEqErr' :: SolverReportErrCtxt
-> ErrorItem
-> (TcId, TcCoercionN)
-> Type
-> TcM TcSolverReportMsg
mkTyVarEqErr' SolverReportErrCtxt
ctxt ErrorItem
item (TcId
tv1, TcCoercionN
co1) Type
ty2
| Just FixedRuntimeRepErrorInfo
frr_info <- Maybe FixedRuntimeRepErrorInfo
mb_concrete_reason
= do
(_, infos) <- ZonkM (TidyEnv, [FixedRuntimeRepErrorInfo])
-> TcM (TidyEnv, [FixedRuntimeRepErrorInfo])
forall a. ZonkM a -> TcM a
liftZonkM (ZonkM (TidyEnv, [FixedRuntimeRepErrorInfo])
-> TcM (TidyEnv, [FixedRuntimeRepErrorInfo]))
-> ZonkM (TidyEnv, [FixedRuntimeRepErrorInfo])
-> TcM (TidyEnv, [FixedRuntimeRepErrorInfo])
forall a b. (a -> b) -> a -> b
$ TidyEnv
-> [FixedRuntimeRepErrorInfo]
-> ZonkM (TidyEnv, [FixedRuntimeRepErrorInfo])
zonkTidyFRRInfos (SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt) [FixedRuntimeRepErrorInfo
frr_info]
return $ FixedRuntimeRepError infos
| CheckTyEqResult
check_eq_result CheckTyEqResult -> CheckTyEqProblem -> Bool
`cterHasProblem` CheckTyEqProblem
cteImpredicative
= do
tyvar_eq_info <- (TcId, Maybe Implication)
-> Type -> IOEnv (Env TcGblEnv TcLclEnv) TyVarInfo
extraTyVarEqInfo (TcId
tv1, Maybe Implication
forall a. Maybe a
Nothing) Type
ty2
let
poly_msg = ErrorItem
-> TcId -> Type -> Maybe TyVarInfo -> CannotUnifyVariableReason
CannotUnifyWithPolytype ErrorItem
item TcId
tv1 Type
ty2 Maybe TyVarInfo
mb_tv_info
mb_tv_info
| TcId -> Bool
isSkolemTyVar TcId
tv1
= TyVarInfo -> Maybe TyVarInfo
forall a. a -> Maybe a
Just TyVarInfo
tyvar_eq_info
| Bool
otherwise
= Maybe TyVarInfo
forall a. Maybe a
Nothing
main_msg =
CannotUnifyVariable
{ mismatchMsg :: MismatchMsg
mismatchMsg = MismatchMsg
headline_msg
, cannotUnifyReason :: CannotUnifyVariableReason
cannotUnifyReason = CannotUnifyVariableReason
poly_msg }
return main_msg
| TcCoercionN -> Bool
hasCoercionHoleCo TcCoercionN
co1 Bool -> Bool -> Bool
|| Type -> Bool
hasCoercionHoleTy Type
ty2
= TcSolverReportMsg -> TcM TcSolverReportMsg
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (TcSolverReportMsg -> TcM TcSolverReportMsg)
-> TcSolverReportMsg -> TcM TcSolverReportMsg
forall a b. (a -> b) -> a -> b
$ ErrorItem -> TcSolverReportMsg
mkBlockedEqErr ErrorItem
item
| 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 EqRel -> EqRel -> Bool
forall a. Eq a => a -> a -> Bool
== EqRel
ReprEq
= do
tv_extra <- (TcId, Maybe Implication)
-> Type -> IOEnv (Env TcGblEnv TcLclEnv) TyVarInfo
extraTyVarEqInfo (TcId
tv1, Maybe Implication
forall a. Maybe a
Nothing) Type
ty2
reason <- if errorItemEqRel item == ReprEq
then RepresentationalEq tv_extra <$> coercible_msg ty1 ty2
else return $ DifferentTyVars tv_extra
let main_msg = CannotUnifyVariable
{ mismatchMsg :: MismatchMsg
mismatchMsg = MismatchMsg
headline_msg
, cannotUnifyReason :: CannotUnifyVariableReason
cannotUnifyReason = CannotUnifyVariableReason
reason }
return main_msg
| TcId
tv1 TcId -> TyCoVarSet -> Bool
`elemVarSet` Type -> TyCoVarSet
tyCoVarsOfType Type
ty2
= let ambiguity_infos :: [AmbiguityInfo]
ambiguity_infos = Type -> Type -> [AmbiguityInfo]
eqInfoMsgs Type
ty1 Type
ty2
interesting_tyvars :: [TcId]
interesting_tyvars = (TcId -> Bool) -> [TcId] -> [TcId]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (TcId -> Bool) -> TcId -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type -> Bool
noFreeVarsOfType (Type -> Bool) -> (TcId -> Type) -> TcId -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TcId -> Type
tyVarKind) ([TcId] -> [TcId]) -> [TcId] -> [TcId]
forall a b. (a -> b) -> a -> b
$
(TcId -> Bool) -> [TcId] -> [TcId]
forall a. (a -> Bool) -> [a] -> [a]
filter TcId -> Bool
isTyVar ([TcId] -> [TcId]) -> [TcId] -> [TcId]
forall a b. (a -> b) -> a -> b
$
FV -> [TcId]
fvVarList (FV -> [TcId]) -> FV -> [TcId]
forall a b. (a -> b) -> a -> b
$
Type -> FV
tyCoFVsOfType Type
ty1 FV -> FV -> FV
`unionFV` Type -> FV
tyCoFVsOfType Type
ty2
occurs_err :: CannotUnifyVariableReason
occurs_err =
OccursCheck
{ occursCheckInterestingTyVars :: [TcId]
occursCheckInterestingTyVars = [TcId]
interesting_tyvars
, occursCheckAmbiguityInfos :: [AmbiguityInfo]
occursCheckAmbiguityInfos = [AmbiguityInfo]
ambiguity_infos }
main_msg :: TcSolverReportMsg
main_msg =
CannotUnifyVariable
{ mismatchMsg :: MismatchMsg
mismatchMsg = MismatchMsg
headline_msg
, cannotUnifyReason :: CannotUnifyVariableReason
cannotUnifyReason = CannotUnifyVariableReason
occurs_err }
in TcSolverReportMsg -> TcM TcSolverReportMsg
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return TcSolverReportMsg
main_msg
| (Implication
implic:[Implication]
_) <- SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt
, Implic { ic_skols :: Implication -> [TcId]
ic_skols = [TcId]
skols } <- Implication
implic
, TcId
tv1 TcId -> [TcId] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [TcId]
skols
= do
tv_extra <- (TcId, Maybe Implication)
-> Type -> IOEnv (Env TcGblEnv TcLclEnv) TyVarInfo
extraTyVarEqInfo (TcId
tv1, Maybe Implication
forall a. Maybe a
Nothing) Type
ty2
let msg = Mismatch
{ mismatchMsg :: MismatchMsg
mismatchMsg = MismatchMsg
mismatch_msg
, mismatchTyVarInfo :: Maybe TyVarInfo
mismatchTyVarInfo = TyVarInfo -> Maybe TyVarInfo
forall a. a -> Maybe a
Just TyVarInfo
tv_extra
, mismatchAmbiguityInfo :: [AmbiguityInfo]
mismatchAmbiguityInfo = []
, mismatchCoercibleInfo :: Maybe CoercibleMsg
mismatchCoercibleInfo = Maybe CoercibleMsg
forall a. Maybe a
Nothing }
return msg
| (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 = (TcId -> Bool) -> [TcId] -> [TcId]
forall a. (a -> Bool) -> [a] -> [a]
filter (TcId -> TyCoVarSet -> Bool
`elemVarSet` (Type -> TyCoVarSet
tyCoVarsOfType Type
ty2)) [TcId]
skols
, Bool -> Bool
not ([TcId] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TcId]
esc_skols)
= let main_msg :: TcSolverReportMsg
main_msg =
CannotUnifyVariable
{ mismatchMsg :: MismatchMsg
mismatchMsg = MismatchMsg
mismatch_msg
, cannotUnifyReason :: CannotUnifyVariableReason
cannotUnifyReason = ErrorItem -> Implication -> [TcId] -> CannotUnifyVariableReason
SkolemEscape ErrorItem
item Implication
implic [TcId]
esc_skols }
in TcSolverReportMsg -> TcM TcSolverReportMsg
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return TcSolverReportMsg
main_msg
| (Implication
implic:[Implication]
_) <- SolverReportErrCtxt -> [Implication]
cec_encl SolverReportErrCtxt
ctxt
, Implic { ic_tclvl :: Implication -> TcLevel
ic_tclvl = TcLevel
lvl } <- Implication
implic
= Bool -> SDoc -> TcM TcSolverReportMsg -> TcM TcSolverReportMsg
forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (Bool -> Bool
not (TcLevel -> TcId -> Bool
isTouchableMetaTyVar TcLevel
lvl TcId
tv1))
(TcId -> SDoc
forall a. Outputable a => a -> SDoc
ppr TcId
tv1 SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ TcLevel -> SDoc
forall a. Outputable a => a -> SDoc
ppr TcLevel
lvl) (TcM TcSolverReportMsg -> TcM TcSolverReportMsg)
-> TcM TcSolverReportMsg -> TcM TcSolverReportMsg
forall a b. (a -> b) -> a -> b
$ do
tv_extra <- (TcId, Maybe Implication)
-> Type -> IOEnv (Env TcGblEnv TcLclEnv) TyVarInfo
extraTyVarEqInfo (TcId
tv1, Implication -> Maybe Implication
forall a. a -> Maybe a
Just Implication
implic) Type
ty2
let tv_extra' = TyVarInfo
tv_extra { thisTyVarIsUntouchable = Just implic }
msg = Mismatch
{ mismatchMsg :: MismatchMsg
mismatchMsg = MismatchMsg
mismatch_msg
, mismatchTyVarInfo :: Maybe TyVarInfo
mismatchTyVarInfo = TyVarInfo -> Maybe TyVarInfo
forall a. a -> Maybe a
Just TyVarInfo
tv_extra'
, mismatchAmbiguityInfo :: [AmbiguityInfo]
mismatchAmbiguityInfo = []
, mismatchCoercibleInfo :: Maybe CoercibleMsg
mismatchCoercibleInfo = Maybe CoercibleMsg
forall a. Maybe a
Nothing }
return msg
| Bool
otherwise
= SolverReportErrCtxt
-> ErrorItem -> Type -> Type -> TcM TcSolverReportMsg
reportEqErr SolverReportErrCtxt
ctxt ErrorItem
item (TcId -> Type
mkTyVarTy TcId
tv1) Type
ty2
where
headline_msg :: MismatchMsg
headline_msg = SolverReportErrCtxt -> ErrorItem -> Type -> Type -> MismatchMsg
misMatchOrCND SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2
mismatch_msg :: MismatchMsg
mismatch_msg = ErrorItem -> Type -> Type -> MismatchMsg
mkMismatchMsg ErrorItem
item 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
isConcreteType Type
ty2)
= FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo
forall a. a -> Maybe a
Just (FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo)
-> FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo
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)
= FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo
forall a. a -> Maybe a
Just (FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo)
-> FixedRuntimeRepErrorInfo -> Maybe FixedRuntimeRepErrorInfo
forall a b. (a -> b) -> a -> b
$ ConcreteTvOrigin -> TcId -> Type -> FixedRuntimeRepErrorInfo
frr_reason ConcreteTvOrigin
frr_orig TcId
tv2 Type
ty1
| Bool
otherwise
= Maybe FixedRuntimeRepErrorInfo
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 = (TcId, Type) -> Maybe (TcId, Type)
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
_ -> CheckTyEqResult
cteOK
eqInfoMsgs :: TcType -> TcType -> [AmbiguityInfo]
eqInfoMsgs :: Type -> Type -> [AmbiguityInfo]
eqInfoMsgs Type
ty1 Type
ty2
= [Maybe AmbiguityInfo] -> [AmbiguityInfo]
forall a. [Maybe a] -> [a]
catMaybes [Maybe AmbiguityInfo
tyfun_msg, Maybe AmbiguityInfo
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@([TcId]
kvs1, [TcId]
tvs1) = Type -> ([TcId], [TcId])
ambigTkvsOfTy Type
ty1
ambig_tkvs2 :: ([TcId], [TcId])
ambig_tkvs2@([TcId]
kvs2, [TcId]
tvs2) = Type -> ([TcId], [TcId])
ambigTkvsOfTy Type
ty2
ambig_tkvs :: ([TcId], [TcId])
ambig_tkvs@([TcId]
ambig_kvs, [TcId]
ambig_tvs)
= case (Maybe TyCon
mb_fun1, Maybe TyCon
mb_fun2) of
(Maybe TyCon
Nothing, Maybe TyCon
Nothing) -> ([], [])
(Just {}, Maybe TyCon
Nothing) -> ([TcId], [TcId])
ambig_tkvs1
(Maybe TyCon
Nothing, Just {}) -> ([TcId], [TcId])
ambig_tkvs2
(Just{},Just{}) -> ([TcId]
kvs1 [TcId] -> [TcId] -> [TcId]
forall a. Eq a => [a] -> [a] -> [a]
`union` [TcId]
kvs2, [TcId]
tvs1 [TcId] -> [TcId] -> [TcId]
forall a. Eq a => [a] -> [a] -> [a]
`union` [TcId]
tvs2)
ambig_msg :: Maybe AmbiguityInfo
ambig_msg | Maybe TyCon -> Bool
forall a. Maybe a -> Bool
isJust Maybe TyCon
mb_fun1 Bool -> Bool -> Bool
|| Maybe TyCon -> Bool
forall a. Maybe a -> Bool
isJust Maybe TyCon
mb_fun2
, Bool -> Bool
not ([TcId] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TcId]
ambig_kvs Bool -> Bool -> Bool
&& [TcId] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TcId]
ambig_tvs)
= AmbiguityInfo -> Maybe AmbiguityInfo
forall a. a -> Maybe a
Just (AmbiguityInfo -> Maybe AmbiguityInfo)
-> AmbiguityInfo -> Maybe AmbiguityInfo
forall a b. (a -> b) -> a -> b
$ Bool -> ([TcId], [TcId]) -> AmbiguityInfo
Ambiguity Bool
False ([TcId], [TcId])
ambig_tkvs
| Bool
otherwise
= Maybe AmbiguityInfo
forall a. Maybe a
Nothing
tyfun_msg :: Maybe AmbiguityInfo
tyfun_msg | Just TyCon
tc1 <- Maybe TyCon
mb_fun1
, Just TyCon
tc2 <- Maybe TyCon
mb_fun2
, TyCon
tc1 TyCon -> TyCon -> Bool
forall a. Eq a => a -> a -> Bool
== TyCon
tc2
, Bool -> Bool
not (TyCon -> Role -> Bool
isInjectiveTyCon TyCon
tc1 Role
Nominal)
= AmbiguityInfo -> Maybe AmbiguityInfo
forall a. a -> Maybe a
Just (AmbiguityInfo -> Maybe AmbiguityInfo)
-> AmbiguityInfo -> Maybe AmbiguityInfo
forall a b. (a -> b) -> a -> b
$ TyCon -> AmbiguityInfo
NonInjectiveTyFam TyCon
tc1
| Bool
otherwise
= Maybe AmbiguityInfo
forall a. Maybe a
Nothing
misMatchOrCND :: SolverReportErrCtxt -> ErrorItem
-> TcType -> TcType -> MismatchMsg
misMatchOrCND :: SolverReportErrCtxt -> ErrorItem -> Type -> Type -> MismatchMsg
misMatchOrCND SolverReportErrCtxt
ctxt ErrorItem
item Type
ty1 Type
ty2
| Bool
insoluble_item
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 CtFlavour -> CtFlavour -> Bool
forall a. Eq a => a -> a -> Bool
== CtFlavour
Given)
Bool -> Bool -> Bool
|| [Implication] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Implication]
givens
=
ErrorItem -> Type -> Type -> MismatchMsg
mkMismatchMsg ErrorItem
item Type
ty1 Type
ty2
| Bool
otherwise
= [Implication]
-> NonEmpty ErrorItem -> Maybe CND_Extra -> MismatchMsg
CouldNotDeduce [Implication]
givens (ErrorItem
item ErrorItem -> [ErrorItem] -> NonEmpty ErrorItem
forall a. a -> [a] -> NonEmpty a
:| []) (CND_Extra -> Maybe CND_Extra
forall a. a -> Maybe a
Just (CND_Extra -> Maybe CND_Extra) -> CND_Extra -> Maybe CND_Extra
forall a b. (a -> b) -> a -> b
$ TypeOrKind -> Type -> Type -> CND_Extra
CND_Extra TypeOrKind
level Type
ty1 Type
ty2)
where
insoluble_item :: Bool
insoluble_item = case ErrorItem -> Maybe CtIrredReason
ei_m_reason ErrorItem
item of
Maybe CtIrredReason
Nothing -> Bool
False
Just CtIrredReason
r -> CtIrredReason -> Bool
isInsolubleReason CtIrredReason
r
level :: TypeOrKind
level = CtLoc -> Maybe TypeOrKind
ctLocTypeOrKind_maybe (ErrorItem -> CtLoc
errorItemCtLoc ErrorItem
item) Maybe TypeOrKind -> TypeOrKind -> TypeOrKind
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 HasGivenEqs -> HasGivenEqs -> Bool
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, Maybe Implication) -> TcType -> TcM TyVarInfo
(TcId
tv1, Maybe Implication
mb_implic) Type
ty2
= do
tv1_info <- TcId -> TcM TcId
extraTyVarInfo TcId
tv1
ty2_info <- ty_extra ty2
return $
TyVarInfo
{ thisTyVar = tv1_info
, thisTyVarIsUntouchable = mb_implic
, otherTy = ty2_info }
where
ty_extra :: Type -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe TcId)
ty_extra Type
ty = case Type -> Maybe (TcId, TcCoercionN)
getCastedTyVar_maybe Type
ty of
Just (TcId
tv, TcCoercionN
_) -> TcId -> Maybe TcId
forall a. a -> Maybe a
Just (TcId -> Maybe TcId)
-> TcM TcId -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe TcId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TcId -> TcM TcId
extraTyVarInfo TcId
tv
Maybe (TcId, TcCoercionN)
Nothing -> Maybe TcId -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe TcId)
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TcId
forall a. Maybe a
Nothing
extraTyVarInfo :: TcTyVar -> TcM TyVar
TcId
tv = Bool -> SDoc -> TcM TcId -> TcM TcId
forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (TcId -> Bool
isTyVar TcId
tv) (TcId -> SDoc
forall a. Outputable a => a -> SDoc
ppr TcId
tv) (TcM TcId -> TcM TcId) -> TcM TcId -> TcM TcId
forall a b. (a -> b) -> a -> b
$
case TcId -> TcTyVarDetails
tcTyVarDetails TcId
tv of
SkolemTv SkolemInfo
skol_info TcLevel
lvl Bool
overlaps -> do
new_skol_info <- ZonkM SkolemInfo -> TcM SkolemInfo
forall a. ZonkM a -> TcM a
liftZonkM (ZonkM SkolemInfo -> TcM SkolemInfo)
-> ZonkM SkolemInfo -> TcM SkolemInfo
forall a b. (a -> b) -> a -> b
$ SkolemInfo -> ZonkM SkolemInfo
zonkSkolemInfo SkolemInfo
skol_info
return $ mkTcTyVar (tyVarName tv) (tyVarKind tv) (SkolemTv new_skol_info lvl overlaps)
TcTyVarDetails
_ -> TcId -> TcM TcId
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return TcId
tv
mkMismatchMsg :: ErrorItem -> Type -> Type -> MismatchMsg
mkMismatchMsg :: ErrorItem -> Type -> Type -> MismatchMsg
mkMismatchMsg ErrorItem
item Type
ty1 Type
ty2 =
case CtOrigin
orig of
TypeEqOrigin { Type
uo_actual :: Type
uo_actual :: CtOrigin -> Type
uo_actual, Type
uo_expected :: Type
uo_expected :: CtOrigin -> Type
uo_expected, uo_thing :: CtOrigin -> Maybe TypedThing
uo_thing = Maybe TypedThing
mb_thing } ->
(TypeEqMismatch
{ 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
, teq_mb_same_occ :: Maybe SameOccInfo
teq_mb_same_occ = Type -> Type -> Maybe SameOccInfo
sameOccExtras Type
ty2 Type
ty1 })
KindEqOrigin Type
cty1 Type
cty2 CtOrigin
sub_o Maybe TypeOrKind
mb_sub_t_or_k -> BasicMismatch
{ mismatch_ea :: MismatchEA
mismatch_ea = MismatchEA
NoEA
, mismatch_item :: ErrorItem
mismatch_item = ErrorItem
item
, mismatch_ty1 :: Type
mismatch_ty1 = Type
ty1
, mismatch_ty2 :: Type
mismatch_ty2 = Type
ty2
, mismatch_whenMatching :: Maybe WhenMatching
mismatch_whenMatching = WhenMatching -> Maybe WhenMatching
forall a. a -> Maybe a
Just (WhenMatching -> Maybe WhenMatching)
-> WhenMatching -> Maybe WhenMatching
forall a b. (a -> b) -> a -> b
$ Type -> Type -> CtOrigin -> Maybe TypeOrKind -> WhenMatching
WhenMatching Type
cty1 Type
cty2 CtOrigin
sub_o Maybe TypeOrKind
mb_sub_t_or_k
, mismatch_mb_same_occ :: Maybe SameOccInfo
mismatch_mb_same_occ = Maybe SameOccInfo
mb_same_occ
}
CtOrigin
_ -> BasicMismatch
{ mismatch_ea :: MismatchEA
mismatch_ea = MismatchEA
NoEA
, mismatch_item :: ErrorItem
mismatch_item = ErrorItem
item
, mismatch_ty1 :: Type
mismatch_ty1 = Type
ty1
, mismatch_ty2 :: Type
mismatch_ty2 = Type
ty2
, mismatch_whenMatching :: Maybe WhenMatching
mismatch_whenMatching = Maybe WhenMatching
forall a. Maybe a
Nothing
, mismatch_mb_same_occ :: Maybe SameOccInfo
mismatch_mb_same_occ = Maybe SameOccInfo
mb_same_occ
}
where
orig :: CtOrigin
orig = ErrorItem -> CtOrigin
errorItemOrigin ErrorItem
item
mb_same_occ :: Maybe SameOccInfo
mb_same_occ = Type -> Type -> Maybe SameOccInfo
sameOccExtras Type
ty2 Type
ty1
sameOccExtras :: TcType -> TcType -> Maybe SameOccInfo
Type
ty1 Type
ty2
| Just (TyCon
tc1, [Type]
_) <- HasDebugCallStack => Type -> Maybe (TyCon, [Type])
Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
ty1
, Just (TyCon
tc2, [Type]
_) <- HasDebugCallStack => Type -> Maybe (TyCon, [Type])
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 OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
== Name -> OccName
nameOccName Name
n2
same_pkg :: Bool
same_pkg = GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit (HasDebugCallStack => Name -> GenModule Unit
Name -> GenModule Unit
nameModule Name
n1) Unit -> Unit -> Bool
forall a. Eq a => a -> a -> Bool
== GenModule Unit -> Unit
forall unit. GenModule unit -> unit
moduleUnit (HasDebugCallStack => Name -> GenModule Unit
Name -> GenModule Unit
nameModule Name
n2)
, Name
n1 Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
/= Name
n2
, Bool
same_occ
= SameOccInfo -> Maybe SameOccInfo
forall a. a -> Maybe a
Just (SameOccInfo -> Maybe SameOccInfo)
-> SameOccInfo -> Maybe SameOccInfo
forall a b. (a -> b) -> a -> b
$ Bool -> Name -> Name -> SameOccInfo
SameOcc Bool
same_pkg Name
n1 Name
n2
| Bool
otherwise
= Maybe SameOccInfo
forall a. Maybe a
Nothing
mkDictErr :: HasDebugCallStack => SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkDictErr :: HasDebugCallStack =>
SolverReportErrCtxt -> NonEmpty ErrorItem -> TcM SolverReport
mkDictErr SolverReportErrCtxt
ctxt NonEmpty ErrorItem
orig_items
= do { inst_envs <- TcM InstEnvs
tcGetInstEnvs
; let min_items = NonEmpty ErrorItem -> [ErrorItem]
elim_superclasses NonEmpty ErrorItem
items
lookups = (ErrorItem -> (ErrorItem, ClsInstLookupResult))
-> [ErrorItem] -> [(ErrorItem, ClsInstLookupResult)]
forall a b. (a -> b) -> [a] -> [b]
map (InstEnvs -> ErrorItem -> (ErrorItem, ClsInstLookupResult)
lookup_cls_inst InstEnvs
inst_envs) [ErrorItem]
min_items
(no_inst_items, overlap_items) = partition is_no_inst lookups
; err <- mk_dict_err ctxt (head (no_inst_items ++ overlap_items))
; return $ important ctxt err }
where
items :: NonEmpty ErrorItem
items = (ErrorItem -> Bool) -> NonEmpty ErrorItem -> NonEmpty ErrorItem
forall a. (a -> Bool) -> NonEmpty a -> NonEmpty a
tryFilter (Bool -> Bool
not (Bool -> Bool) -> (ErrorItem -> Bool) -> ErrorItem -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorItem -> Bool
ei_suppress) NonEmpty ErrorItem
orig_items
no_givens :: Bool
no_givens = [Implication] -> Bool
forall a. [a] -> Bool
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
&& [InstMatch] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [InstMatch]
matches
Bool -> Bool -> Bool
&& (PotentialUnifiers -> Bool
nullUnifiers PotentialUnifiers
unifiers Bool -> Bool -> Bool
|| (TcId -> Bool) -> [TcId] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool -> Bool
not (Bool -> Bool) -> (TcId -> Bool) -> TcId -> Bool
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])
Type -> (Class, [Type])
getClassPredTys (ErrorItem -> Type
errorItemPred ErrorItem
item)
elim_superclasses :: NonEmpty ErrorItem -> [ErrorItem]
elim_superclasses = (ErrorItem -> Type) -> [ErrorItem] -> [ErrorItem]
forall a. (a -> Type) -> [a] -> [a]
mkMinimalBySCs ErrorItem -> Type
errorItemPred ([ErrorItem] -> [ErrorItem])
-> (NonEmpty ErrorItem -> [ErrorItem])
-> NonEmpty ErrorItem
-> [ErrorItem]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty ErrorItem -> [ErrorItem]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList
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)) = case ([InstMatch] -> Maybe (NonEmpty InstMatch)
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty [InstMatch]
matches, [InstMatch] -> Maybe (NonEmpty InstMatch)
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty [InstMatch]
unsafe_overlapped) of
(Maybe (NonEmpty InstMatch)
Nothing, Maybe (NonEmpty InstMatch)
_) -> do
{ (_, rel_binds, item) <- Bool
-> SolverReportErrCtxt
-> ErrorItem
-> TcM (SolverReportErrCtxt, RelevantBindings, ErrorItem)
relevantBindings Bool
True SolverReportErrCtxt
ctxt ErrorItem
item
; candidate_insts <- get_candidate_instances
; (imp_errs, field_suggestions) <- record_field_suggestions item
; return (cannot_resolve_msg item candidate_insts rel_binds imp_errs field_suggestions) }
(Just NonEmpty InstMatch
matchesNE, Maybe (NonEmpty InstMatch)
Nothing) -> TcSolverReportMsg -> TcM TcSolverReportMsg
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (TcSolverReportMsg -> TcM TcSolverReportMsg)
-> TcSolverReportMsg -> TcM TcSolverReportMsg
forall a b. (a -> b) -> a -> b
$
ErrorItem -> NonEmpty ClsInst -> [ClsInst] -> TcSolverReportMsg
OverlappingInstances ErrorItem
item ((InstMatch -> ClsInst) -> NonEmpty InstMatch -> NonEmpty ClsInst
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map InstMatch -> ClsInst
forall a b. (a, b) -> a
fst NonEmpty InstMatch
matchesNE) (PotentialUnifiers -> [ClsInst]
getCoherentUnifiers PotentialUnifiers
unifiers)
(Just (InstMatch
match :| []), Just NonEmpty InstMatch
unsafe_overlappedNE) -> TcSolverReportMsg -> TcM TcSolverReportMsg
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (TcSolverReportMsg -> TcM TcSolverReportMsg)
-> TcSolverReportMsg -> TcM TcSolverReportMsg
forall a b. (a -> b) -> a -> b
$
ErrorItem -> ClsInst -> NonEmpty ClsInst -> TcSolverReportMsg
UnsafeOverlap ErrorItem
item (InstMatch -> ClsInst
forall a b. (a, b) -> a
fst InstMatch
match) ((InstMatch -> ClsInst) -> NonEmpty InstMatch -> NonEmpty ClsInst
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map InstMatch -> ClsInst
forall a b. (a, b) -> a
fst NonEmpty InstMatch
unsafe_overlappedNE)
(Just matches :: NonEmpty InstMatch
matches@(InstMatch
_ :| [InstMatch]
_), Just NonEmpty InstMatch
overlaps) -> String -> SDoc -> TcM TcSolverReportMsg
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"mk_dict_err: multiple matches with overlap" (SDoc -> TcM TcSolverReportMsg) -> SDoc -> TcM TcSolverReportMsg
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"matches:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> NonEmpty InstMatch -> SDoc
forall a. Outputable a => a -> SDoc
ppr NonEmpty InstMatch
matches, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"overlaps:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> NonEmpty InstMatch -> SDoc
forall a. Outputable a => a -> SDoc
ppr NonEmpty InstMatch
overlaps ]
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])
Type -> (Class, [Type])
getClassPredTys Type
pred
get_candidate_instances :: TcM [ClsInst]
get_candidate_instances :: TcM [ClsInst]
get_candidate_instances
| [Type
ty] <- [Type]
tys
= do { instEnvs <- TcM InstEnvs
tcGetInstEnvs
; return (filter (is_candidate_inst ty)
(classInstances instEnvs clas)) }
| Bool
otherwise = [ClsInst] -> TcM [ClsInst]
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
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]
_) <- HasDebugCallStack => Type -> Maybe (TyCon, [Type])
Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
ty
, Just (TyCon
tc2, [Type]
_) <- HasDebugCallStack => Type -> Maybe (TyCon, [Type])
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 Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
/= Name
n2
same_occ_names :: Bool
same_occ_names = Name -> OccName
nameOccName Name
n1 OccName -> OccName -> Bool
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 :: ErrorItem -> TcM ([ImportError], [GhcHint])
record_field_suggestions :: ErrorItem -> RnM ([ImportError], [GhcHint])
record_field_suggestions ErrorItem
item = ((OccName -> RnM ([ImportError], [GhcHint]))
-> Maybe OccName -> RnM ([ImportError], [GhcHint]))
-> Maybe OccName
-> (OccName -> RnM ([ImportError], [GhcHint]))
-> RnM ([ImportError], [GhcHint])
forall a b c. (a -> b -> c) -> b -> a -> c
flip (RnM ([ImportError], [GhcHint])
-> (OccName -> RnM ([ImportError], [GhcHint]))
-> Maybe OccName
-> RnM ([ImportError], [GhcHint])
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (RnM ([ImportError], [GhcHint])
-> (OccName -> RnM ([ImportError], [GhcHint]))
-> Maybe OccName
-> RnM ([ImportError], [GhcHint]))
-> RnM ([ImportError], [GhcHint])
-> (OccName -> RnM ([ImportError], [GhcHint]))
-> Maybe OccName
-> RnM ([ImportError], [GhcHint])
forall a b. (a -> b) -> a -> b
$ ([ImportError], [GhcHint]) -> RnM ([ImportError], [GhcHint])
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return ([], [GhcHint]
noHints)) Maybe OccName
record_field ((OccName -> RnM ([ImportError], [GhcHint]))
-> RnM ([ImportError], [GhcHint]))
-> (OccName -> RnM ([ImportError], [GhcHint]))
-> RnM ([ImportError], [GhcHint])
forall a b. (a -> b) -> a -> b
$ \OccName
name ->
do { glb_env <- TcRn GlobalRdrEnv
getGlobalRdrEnv
; lcl_env <- getLocalRdrEnv
; let field_name_hints = ErrorItem -> [GhcHint]
report_no_fieldnames ErrorItem
item
; (errs, hints) <- if occ_name_in_scope glb_env lcl_env name
then return ([], noHints)
else unknownNameSuggestions emptyLocalRdrEnv WL_RecField (mkRdrUnqual name)
; pure (errs, hints ++ field_name_hints)
}
report_no_fieldnames :: ErrorItem -> [GhcHint]
report_no_fieldnames :: ErrorItem -> [GhcHint]
report_no_fieldnames ErrorItem
item
| Just (EvVarDest TcId
evvar) <- ErrorItem -> Maybe TcEvDest
ei_evdest ErrorItem
item
, Just (TyCon
_, [Type
_symbol, Type
x, Type
r, Type
a]) <- HasDebugCallStack => Type -> Maybe (TyCon, [Type])
Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe (TcId -> Type
varType TcId
evvar)
, Just (TyCon
r_tycon, [Type]
_) <- HasDebugCallStack => Type -> Maybe (TyCon, [Type])
Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
r
, Just FastString
x_name <- Type -> Maybe FastString
isStrLitTy Type
x
, Bool -> Bool
not (Bool -> Bool) -> ([FieldLabel] -> Bool) -> [FieldLabel] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FieldLabel] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([FieldLabel] -> Bool) -> [FieldLabel] -> Bool
forall a b. (a -> b) -> a -> b
$ TyCon -> [FieldLabel]
tyConFieldLabels TyCon
r_tycon
= [FastString -> Type -> Type -> GhcHint
RemindRecordMissingField FastString
x_name Type
r Type
a]
| Bool
otherwise = []
occ_name_in_scope :: GlobalRdrEnv -> LocalRdrEnv -> OccName -> Bool
occ_name_in_scope GlobalRdrEnv
glb_env LocalRdrEnv
lcl_env OccName
occ_name = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$
[GlobalRdrEltX GREInfo] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (GlobalRdrEnv -> LookupGRE GREInfo -> [GlobalRdrEltX GREInfo]
forall info.
GlobalRdrEnvX info -> LookupGRE info -> [GlobalRdrEltX info]
lookupGRE GlobalRdrEnv
glb_env (OccName -> WhichGREs GREInfo -> LookupGRE GREInfo
forall info. OccName -> WhichGREs info -> LookupGRE info
LookupOccName OccName
occ_name (FieldsOrSelectors -> WhichGREs GREInfo
RelevantGREsFOS FieldsOrSelectors
WantNormal))) Bool -> Bool -> Bool
&&
Maybe Name -> 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
GetFieldOrigin FastString
name -> OccName -> Maybe OccName
forall a. a -> Maybe a
Just (FastString -> OccName
mkVarOccFS FastString
name)
CtOrigin
_ -> Maybe OccName
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]
getCoherentUnifiers PotentialUnifiers
unifiers) [ClsInst]
candidate_insts [ImportError]
imp_errs [GhcHint]
field_suggestions RelevantBindings
binds
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" (ErrorItem -> SDoc
forall a. Outputable a => a -> SDoc
ppr ErrorItem
item)
; (env1, tidy_orig) <- ZonkM (TidyEnv, CtOrigin) -> TcM (TidyEnv, CtOrigin)
forall a. ZonkM a -> TcM a
liftZonkM (ZonkM (TidyEnv, CtOrigin) -> TcM (TidyEnv, CtOrigin))
-> ZonkM (TidyEnv, CtOrigin) -> TcM (TidyEnv, CtOrigin)
forall a b. (a -> b) -> a -> b
$ TidyEnv -> CtOrigin -> ZonkM (TidyEnv, CtOrigin)
zonkTidyOrigin (SolverReportErrCtxt -> TidyEnv
cec_tidy SolverReportErrCtxt
ctxt) (CtLoc -> CtOrigin
ctLocOrigin CtLoc
loc)
; let 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 = Type -> TyCoVarSet
tyCoVarsOfType (ErrorItem -> Type
errorItemPred ErrorItem
item) TyCoVarSet -> TyCoVarSet -> TyCoVarSet
`unionVarSet` TyCoVarSet
extra_tvs
loc' = CtLoc -> CtOrigin -> CtLoc
setCtLocOrigin CtLoc
loc CtOrigin
tidy_orig
item' = ErrorItem
item { ei_loc = loc' }
; (env2, lcl_name_cache) <- liftZonkM $ zonkTidyTcLclEnvs env1 [lcl_env]
; relev_bds <- relevant_bindings want_filtering lcl_env lcl_name_cache ct_fvs
; let ctxt' = SolverReportErrCtxt
ctxt { cec_tidy = env2 }
; return (ctxt', relev_bds, item') }
where
loc :: CtLoc
loc = ErrorItem -> CtLoc
errorItemCtLoc ErrorItem
item
lcl_env :: CtLocEnv
lcl_env = CtLoc -> CtLocEnv
ctLocEnv CtLoc
loc
relevant_bindings :: Bool
-> CtLocEnv
-> NameEnv Type
-> TyCoVarSet
-> TcM RelevantBindings
relevant_bindings :: Bool
-> CtLocEnv -> NameEnv Type -> TyCoVarSet -> TcM RelevantBindings
relevant_bindings Bool
want_filtering CtLocEnv
lcl_env NameEnv Type
lcl_name_env TyCoVarSet
ct_tvs
= do { dflags <- IOEnv (Env TcGblEnv TcLclEnv) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
; traceTc "relevant_bindings" $
vcat [ ppr ct_tvs
, pprWithCommas id [ ppr id <+> dcolon <+> ppr (idType id)
| TcIdBndr id _ <- ctl_bndrs lcl_env ]
, pprWithCommas id
[ ppr id | TcIdBndr_ExpType id _ _ <- ctl_bndrs lcl_env ] ]
; go dflags (maxRelevantBinds dflags)
emptyVarSet (RelevantBindings [] False)
(removeBindingShadowing $ ctl_bndrs 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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0
dec_max :: Maybe Int -> Maybe Int
dec_max :: Maybe Int -> Maybe Int
dec_max = (Int -> Int) -> Maybe Int -> Maybe Int
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int
n -> Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
go :: DynFlags -> Maybe Int -> TcTyVarSet
-> RelevantBindings
-> [TcBinder]
-> TcM RelevantBindings
go :: DynFlags
-> Maybe Int
-> TyCoVarSet
-> RelevantBindings
-> [TcBinder]
-> TcM RelevantBindings
go DynFlags
_ Maybe Int
_ TyCoVarSet
_ (RelevantBindings [(Name, Type)]
bds Bool
discards) []
= RelevantBindings -> TcM RelevantBindings
forall a. a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. Monad m => a -> m a
return (RelevantBindings -> TcM RelevantBindings)
-> RelevantBindings -> TcM RelevantBindings
forall a b. (a -> b) -> a -> b
$ [(Name, Type)] -> Bool -> RelevantBindings
RelevantBindings ([(Name, Type)] -> [(Name, Type)]
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 : [TcBinder]
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 { mb_ty <- IO (Maybe Type) -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe Type)
forall a. IO a -> IOEnv (Env TcGblEnv TcLclEnv) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Type) -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe Type))
-> IO (Maybe Type) -> IOEnv (Env TcGblEnv TcLclEnv) (Maybe Type)
forall a b. (a -> b) -> a -> b
$ ExpType -> IO (Maybe Type)
forall (m :: * -> *). MonadIO m => ExpType -> m (Maybe Type)
readExpType_maybe ExpType
et
; case 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
-> [TcBinder]
-> TcM RelevantBindings
go DynFlags
dflags Maybe Int
n_left TyCoVarSet
tvs_seen RelevantBindings
rels [TcBinder]
tc_bndrs
go2 :: Name -> TopLevelFlag -> TcM RelevantBindings
go2 Name
id_name TopLevelFlag
top_lvl
= do { let tidy_ty :: Type
tidy_ty = case NameEnv Type -> Name -> Maybe Type
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 -> String -> SDoc -> Type
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"relevant_bindings" (Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
id_name)
; String -> SDoc -> TcM ()
traceTc String
"relevantBindings 1" (Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
id_name SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
dcolon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Type -> 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 (Maybe Int -> Bool
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
-> [TcBinder]
-> TcM RelevantBindings
go DynFlags
dflags Maybe Int
n_left TyCoVarSet
tvs_seen ([(Name, Type)] -> Bool -> RelevantBindings
RelevantBindings [(Name, Type)]
bds Bool
True)
[TcBinder]
tc_bndrs
else DynFlags
-> Maybe Int
-> TyCoVarSet
-> RelevantBindings
-> [TcBinder]
-> 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)
bd(Name, Type) -> [(Name, Type)] -> [(Name, Type)]
forall a. a -> [a] -> [a]
:[(Name, Type)]
bds) Bool
discards) [TcBinder]
tc_bndrs }
warnDefaulting :: [Ct] -> TcTyVar -> Type -> TcM ()
warnDefaulting :: [Ct] -> TcId -> Type -> TcM ()
warnDefaulting [] TcId
_ Type
_
= String -> TcM ()
forall a. HasCallStack => String -> a
panic String
"warnDefaulting: empty Wanteds"
warnDefaulting wanteds :: [Ct]
wanteds@(Ct
ct:[Ct]
_) TcId
the_tv Type
default_ty
= do { warn_default <- WarningFlag -> TcRnIf TcGblEnv TcLclEnv Bool
forall gbl lcl. WarningFlag -> TcRnIf gbl lcl Bool
woptM WarningFlag
Opt_WarnTypeDefaults
; env0 <- liftZonkM $ tcInitTidyEnv
; let filtered = (Ct -> Bool) -> [Ct] -> [Ct]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Ct -> Bool) -> Ct -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CtOrigin -> Bool
isWantedSuperclassOrigin (CtOrigin -> Bool) -> (Ct -> CtOrigin) -> Ct -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ct -> CtOrigin
ctOrigin) [Ct]
wanteds
tidy_env = TidyEnv -> [TcId] -> TidyEnv
tidyFreeTyCoVars TidyEnv
env0 ([TcId] -> TidyEnv) -> [TcId] -> TidyEnv
forall a b. (a -> b) -> a -> b
$
Cts -> [TcId]
tyCoVarsOfCtsList ([Ct] -> Cts
forall a. [a] -> Bag a
listToBag [Ct]
filtered)
tidy_wanteds = (Ct -> Ct) -> [Ct] -> [Ct]
forall a b. (a -> b) -> [a] -> [b]
map (TidyEnv -> Ct -> Ct
tidyCt TidyEnv
tidy_env) [Ct]
filtered
tidy_tv = UniqFM TcId TcId -> TcId -> Maybe TcId
forall a. VarEnv a -> TcId -> Maybe a
lookupVarEnv (TidyEnv -> UniqFM TcId TcId
forall a b. (a, b) -> b
snd TidyEnv
tidy_env) TcId
the_tv
diag = [Ct] -> Maybe TcId -> Type -> TcRnMessage
TcRnWarnDefaulting [Ct]
tidy_wanteds Maybe TcId
tidy_tv Type
default_ty
loc = Ct -> CtLoc
ctLoc Ct
ct
; setCtLocM loc $ diagnosticTc warn_default diag }
solverReportMsg_ExpectedActuals :: TcSolverReportMsg -> Maybe (Type, Type)
solverReportMsg_ExpectedActuals :: TcSolverReportMsg -> Maybe (Type, Type)
solverReportMsg_ExpectedActuals
= \case
Mismatch { mismatchMsg :: TcSolverReportMsg -> MismatchMsg
mismatchMsg = MismatchMsg
mismatch_msg } ->
MismatchMsg -> Maybe (Type, Type)
mismatchMsg_ExpectedActuals MismatchMsg
mismatch_msg
TcSolverReportMsg
_ -> Maybe (Type, Type)
forall a. Maybe a
Nothing
tryFilter :: (a -> Bool) -> NonEmpty a -> NonEmpty a
tryFilter :: forall a. (a -> Bool) -> NonEmpty a -> NonEmpty a
tryFilter a -> Bool
f NonEmpty a
as = NonEmpty a -> Maybe (NonEmpty a) -> NonEmpty a
forall a. a -> Maybe a -> a
fromMaybe NonEmpty a
as (Maybe (NonEmpty a) -> NonEmpty a)
-> Maybe (NonEmpty a) -> NonEmpty a
forall a b. (a -> b) -> a -> b
$ [a] -> Maybe (NonEmpty a)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty ((a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
filter a -> Bool
f (NonEmpty a -> [a]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty a
as))