[Haskell-cafe] Data.Data and OverlappingInstances

oleg at okmij.org oleg at okmij.org
Sat Aug 11 10:05:31 CEST 2012


Timo von Holtz wrote:

> class Test a where
>   foo :: Monad m => m a
>
> instance Num a => Test a where
>   foo = return 1
>
> instance Test Int where
>   foo = return 2
>
> test constr = fromConstrM foo constr

I'm afraid the type checker is right. From the type of fromConstrM
  fromConstrM :: forall m a. (Monad m, Data a) => (forall d. Data d => m d)
    -> Constr -> m a

we see its first argument has the type
	(forall d. Data d => m d)

If instead it had the type 
	(forall d. Test d => m d)

we would have no problem. As it is, when you pass 'foo' of the type
	(Test d, Monad m) => m d
as the first argument of fromConstrM, which only assures the Data d
constraint on 'd' and _nothing_ else, the compiler checks if it can get
rid of (discharge) the constraint Test d. That is, the compiler is
forced to choose an instance for Test. But there is not information to
do that.

Overlapping here is irrelevant. If you had non-overlapping instances

> class Test a where
>   foo :: Monad m => m a
>
> instance Num a => Test [a] where
>   foo = return [1]
>
> instance Test Int where
>   foo = return 2
>
> test constr = fromConstrM foo constr

'test' still causes the problem. The error message now describes the
real problem:

    Could not deduce (Test d) arising from a use of `foo'
    from the context (Monad m, Data a)
      bound by the inferred type of
               test :: (Monad m, Data a) => Constr -> m a
      at /tmp/d.hs:16:1-36
    or from (Data d)
      bound by a type expected by the context: Data d => m d
      at /tmp/d.hs:16:15-36
    Possible fix:
      add (Test d) to the context of
        a type expected by the context: Data d => m d
        or the inferred type of test :: (Monad m, Data a) => Constr -> m a
    In the first argument of `fromConstrM', namely `foo'

and it recommends the right fix: change the type of fromConstrM to be

  fromConstrM :: forall m a. (Monad m, Data a) => 
	( forall d. (Test d, Data d) => m d) -> Constr -> m a

That will solve the problem. Alas, fromConstrM is a library function
and we are not at liberty to change its type.

> Right now I use a "case (typeOf x) of" kind of construct
That is precisely the right way to use Data. SYB provides good
combinators for building functions (generic producers) of that sort.
But you never need unSafeCoerce: gcast is sufficient.







More information about the Haskell-Cafe mailing list