Why isn't this Overlapping?
Anthony Clayden
anthony_clayden at clear.net.nz
Sun Apr 16 07:13:04 UTC 2017
--ghc 7.10 or 8.0.1
{-# LANGUAGE DataKinds, KindSignatures, GADTs,
MultiParamTypeClasses,
FunctionalDependencies, FlexibleInstances,
UndecidableInstances,
NoOverlappingInstances #-}
class TypeEq a a' (b :: Bool) | a a' -> b
instance (b ~ True) => TypeEq a a b
instance (b ~ False) => TypeEq a a' b
Those two instance heads are nearly identical, surely they
overlap?
And for a type-level type equality test, they must be
unifiable.
But GHC doesn't complain.
If I take off the FunDep, then GHC complains.
AFAICT none of those extensions imply Overlaps,
but to be sure I've put NoOverlapping.
AntC
More information about the Glasgow-haskell-users
mailing list