{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE UndecidableInstances #-}
import Data.Data
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.hs:15:26:
Overlapping instances for Test d
arising from a use of `foo' at test.hs:15:26-28
Matching instances:
instance [overlap ok] (Num a) => Test a
-- Defined at test.hs:9:9-23
instance [overlap ok] Test Int -- Defined at test.hs:12:9-16
(The choice depends on the instantiation of `d'
To pick the first instance above, use -XIncoherentInstances
when compiling the other instance declarations)
In the first argument of `fromConstrM', namely `foo'
In the expression: fromConstrM foo constr
In the definition of `test': test constr = fromConstrM foo constr
Failed, modules loaded: none.
Is there a way out? Right now I use a "case (typeOf x) of" kind of construct, but it gets pretty messy and I even have to unsafeCoerce at one point.