[GHC] #14132: Report an error for a missing class instance before an error for type family instances of an associated type.
GHC
ghc-devs at haskell.org
Tue Aug 22 21:43:51 UTC 2017
#14132: Report an error for a missing class instance before an error for type
family instances of an associated type.
-------------------------------------+-------------------------------------
Reporter: duog | Owner: duog
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.2.1
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by duog):
I had a go at this yesterday, but I ran into a problem. There is a comment
on report1:
{{{
-- report1: ones that should *not* be suppresed by
-- an insoluble somewhere else in the tree
-- It's crucial that anything that is considered insoluble
-- (see TcRnTypes.trulyInsoluble) is caught here, otherwise
-- we might suppress its error message, and proceed on past
-- type checking to get a Lint error later
}}}
This means moving `ReporterSpec`s between report1 and report2 doesn't work
as is. It would be possible to make it work by adding some complexity to
the suppression logic; make `ReporterSpec`s in report2 unable to suppress
`ReporterSpec`s in report1.
Alternatively, I think I see how to suppress the equality error in favour
of the class instance error:
The tuples in report1 and report2 are of type `ReporterSpec`:
{{{
type Reporter
= ReportErrCtxt -> [Ct] -> TcM ()
type ReporterSpec
= ( String -- Name
, Ct -> PredTree -> Bool -- Pick these ones
, Bool -- True <=> suppress subsequent reporters
, Reporter) -- The reporter itself
}}}
In `tryReporter`, the current list of unsatisfiable constraints is
partitioned with the 2nd member of the tuple. The matching constraints are
passed to the `Reporter`, and the non-matching constraints are returned
for the next iteration of `tryReporter`.
I propose to change the definition to:
{{{
type Reporter
= ReportErrCtxt -> [Ct] -> TcM [Ct]
type ReporterSpec
= ( String -- Name
, Bool -- True <=> suppress subsequent reporters
, Reporter) -- The reporter itself
}}}
Now the partitioning will be done inside the `Reporter`, and we can write
something like:
{{{
associated_type_eq :: Reporter
associated_type_eq ctxt cts =
let associated_type_cts =
[ (tf_ct, dict_cts)
| tf_ct <- cts
, EqPred NomEq ty1 _ <- [classifyPredType (ctPred ct)]
, (FamilyTyCon{famTcParent = Just cls}, tf_tys) <- ["some function
1" ty1]
, let dict_cts =
[ ct'
| ct' <- cts
, ClassPred cls' cls_tys <- [classifyPredType (ctPred ct)]
, cls' == cls && tf_tys "some function 2" cls_tys
]
]
yeses = [x
| (tf_ct, dict_cts) <- associated_type_cts
, x <- tf_ct : dict_cts
]
noes = filter (`notElem` yeses) cts
in do
mkGroupReporter mkDictErr ctxt $
concat [dict_cts | (_, dict_cts) <- associated_type_cts]
return noes
}}}
where "some function 1" gives the type constructor and it's arguments, and
"some function 2" checks that this associated type comes from this
instance. These functions must exist right?
Do you know of any other cases that could be improved by this more
powerful factoring?
This would affect tracing, since currently in `tryReporter` the
partitioning is done, and if the predicate matches anything `tryReporter`
traces the `Ct`s that matched. With the partitioning inside the `Reporter`
this doesn't work anymore. Perhaps the `Reporter` could also return the
yeses.
Please let me know whether you think this is a good idea, otherwise I will
go ahead and
do the simpler option of adding some complexity to the suppression logic.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14132#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list