Skip to content
Snippets Groups Projects
Commit 358b3c05 authored by Richard Eisenberg's avatar Richard Eisenberg Committed by Austin Seipp
Browse files

Remove code reporting issues with Safe Haskell and coerce.

This is a followup to the fix for #8827, and should be merged
with that change.

(cherry picked from commit 7602bd4d)
parent c00406c0
No related branches found
No related tags found
No related merge requests found
......@@ -995,9 +995,8 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell))
= do { let (is_ambig, ambig_msg) = mkAmbigMsg ct
; (ctxt, binds_msg) <- relevantBindings True ctxt ct
; traceTc "mk_dict_err" (ppr ct $$ ppr is_ambig $$ ambig_msg)
; safe_mod <- safeLanguageOn `fmap` getDynFlags
; rdr_env <- getGlobalRdrEnv
; return (ctxt, cannot_resolve_msg safe_mod rdr_env is_ambig binds_msg ambig_msg) }
; return (ctxt, cannot_resolve_msg rdr_env is_ambig binds_msg ambig_msg) }
| not safe_haskell -- Some matches => overlap errors
= return (ctxt, overlap_msg)
......@@ -1012,8 +1011,8 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell))
givens = getUserGivens ctxt
all_tyvars = all isTyVarTy tys
cannot_resolve_msg safe_mod rdr_env has_ambig_tvs binds_msg ambig_msg
= vcat [ addArising orig (no_inst_msg $$ coercible_explanation safe_mod rdr_env)
cannot_resolve_msg rdr_env has_ambig_tvs binds_msg ambig_msg
= vcat [ addArising orig (no_inst_msg $$ coercible_explanation rdr_env)
, vcat (pp_givens givens)
, ppWhen (has_ambig_tvs && not (null unifiers && null givens))
(vcat [ ambig_msg, binds_msg, potential_msg ])
......@@ -1138,27 +1137,12 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell))
-- This function tries to reconstruct why a "Coercible ty1 ty2" constraint
-- is left over. Therefore its logic has to stay in sync with
-- getCoericbleInst in TcInteract. See Note [Coercible Instances]
coercible_explanation safe_mod rdr_env
coercible_explanation rdr_env
| clas /= coercibleClass = empty
| Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1,
Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2,
tc1 == tc2
= nest 2 $ vcat $
-- Only for safe haskell: First complain if tc is abstract, only if
-- not check if the type constructors therein are abstract
(if safe_mod
then case tyConAbstractMsg rdr_env tc1 empty of
Just msg ->
[ msg $$ ptext (sLit "as required in SafeHaskell mode") ]
Nothing ->
[ msg
| tc <- tyConsOfTyCon tc1
, Just msg <- return $
tyConAbstractMsg rdr_env tc $
parens $ ptext (sLit "used within") <+> quotes (ppr tc1)
]
else []
) ++
[ fsep [ hsep [ ptext $ sLit "because the", speakNth n, ptext $ sLit "type argument"]
, hsep [ ptext $ sLit "of", quotes (ppr tc1), ptext $ sLit "has role Nominal,"]
, ptext $ sLit "but the arguments"
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment