
There is a limited set of situations where the new signatures can fail to
infer, where it would infer before.
This can happen when you construct a Foldable/Traversable value using
polymorphic tools (like Read) that were previously instantiated for list,
but where since foldr et al. are now polymorphic, this doesn't give enough
information for it to know that [] is the instance you wanted.
Ultimately, there is, of course, a balancing act between flexibility and
inference.
I can at least say that the incident rate for cases seems to be very low,
especially when it is contrasted against the pain users have had with using
the existing Foldable/Traversable imports where virtually everything in
them collided with less useful versions of the same combinator (e.g. mapM)
from the Prelude that a dozen other modules (e.g. Control.Monad and
virtually every module in mtl) insisted on re-exporting, making it a game
of whack-a-mole to try to hide them.
The fix here is to supply a manual type signature on the helper.
-Edward
On Tue, Jan 20, 2015 at 6:20 AM, Björn Peemöller wrote: I just discovered that the following program compiled fine using GHC
7.8.4 but was rejected by GHC 7.10.1-rc1: ~~~
data List a = Nil | Cons a (List a) instance Read a => Read (List a) where
readsPrec d s = map convert (readsPrec d s)
where
convert (xs, s2) = (foldr Cons Nil xs, s2)
~~~ GHC 7.10 now complains: ~~~
Read.hs:5:23:
Could not deduce (Foldable t0) arising from a use of ‘convert’
from the context (Read a)
bound by the instance declaration at Read.hs:4:10-32
The type variable ‘t0’ is ambiguous
Note: there are several potential instances:
instance Foldable (Either a) -- Defined in ‘Data.Foldable’
instance Foldable Data.Proxy.Proxy -- Defined in ‘Data.Foldable’
instance GHC.Arr.Ix i => Foldable (GHC.Arr.Array i)
-- Defined in ‘Data.Foldable’
...plus three others
In the first argument of ‘map’, namely ‘convert’
In the expression: map convert (readsPrec d s)
In an equation for ‘readsPrec’:
readsPrec d s
= map convert (readsPrec d s)
where
convert (xs, s2) = (foldr Cons Nil xs, s2) Read.hs:5:32:
Could not deduce (Read (t0 a)) arising from a use of ‘readsPrec’
from the context (Read a)
bound by the instance declaration at Read.hs:4:10-32
The type variable ‘t0’ is ambiguous
Relevant bindings include
readsPrec :: Int -> ReadS (List a) (bound at Read.hs:5:3)
Note: there are several potential instances:
instance (Read a, Read b) => Read (Either a b)
-- Defined in ‘Data.Either’
instance forall (k :: BOX) (s :: k). Read (Data.Proxy.Proxy s)
-- Defined in ‘Data.Proxy’
instance (GHC.Arr.Ix a, Read a, Read b) => Read (GHC.Arr.Array a b)
-- Defined in ‘GHC.Read’
...plus 18 others
In the second argument of ‘map’, namely ‘(readsPrec d s)’
In the expression: map convert (readsPrec d s)
In an equation for ‘readsPrec’:
readsPrec d s
= map convert (readsPrec d s)
where
convert (xs, s2) = (foldr Cons Nil xs, s2)
~~~ The reason is the usage of foldr, which changed its type from foldr :: (a -> b -> b) -> b -> [a] -> b -- GHC 7.8.4 to foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b -- GHC 7.10.1 Thus, the use of foldr is now ambiguous. I can fix this by providing a
type signature convert :: ([a], String) -> (List a, String) However, is this breaking change intended? Regards,
Björn _______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users