<div dir="ltr"><div>There is a limited set of situations where the new signatures can fail to infer, where it would infer before. </div><div><br></div><div>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.</div><div><br></div><div>Ultimately, there is, of course, a balancing act between flexibility and inference.</div><div><br></div><div>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.</div><div><br></div><div>The fix here is to supply a manual type signature on the helper.</div><div><br></div><div>-Edward</div></div><div class="gmail_extra"><br><div class="gmail_quote">On Tue, Jan 20, 2015 at 6:20 AM, Björn Peemöller <span dir="ltr"><<a href="mailto:bjp@informatik.uni-kiel.de" target="_blank">bjp@informatik.uni-kiel.de</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">I just discovered that the following program compiled fine using GHC<br>
7.8.4 but was rejected by GHC 7.10.1-rc1:<br>
<br>
~~~<br>
data List a = Nil | Cons a (List a)<br>
<br>
instance Read a => Read (List a) where<br>
  readsPrec d s = map convert (readsPrec d s)<br>
    where<br>
    convert (xs, s2) = (foldr Cons Nil xs, s2)<br>
~~~<br>
<br>
GHC 7.10 now complains:<br>
<br>
~~~<br>
Read.hs:5:23:<br>
    Could not deduce (Foldable t0) arising from a use of ‘convert’<br>
    from the context (Read a)<br>
      bound by the instance declaration at Read.hs:4:10-32<br>
    The type variable ‘t0’ is ambiguous<br>
    Note: there are several potential instances:<br>
      instance Foldable (Either a) -- Defined in ‘Data.Foldable’<br>
      instance Foldable Data.Proxy.Proxy -- Defined in ‘Data.Foldable’<br>
      instance GHC.Arr.Ix i => Foldable (GHC.Arr.Array i)<br>
        -- Defined in ‘Data.Foldable’<br>
      ...plus three others<br>
    In the first argument of ‘map’, namely ‘convert’<br>
    In the expression: map convert (readsPrec d s)<br>
    In an equation for ‘readsPrec’:<br>
        readsPrec d s<br>
          = map convert (readsPrec d s)<br>
          where<br>
              convert (xs, s2) = (foldr Cons Nil xs, s2)<br>
<br>
Read.hs:5:32:<br>
    Could not deduce (Read (t0 a)) arising from a use of ‘readsPrec’<br>
    from the context (Read a)<br>
      bound by the instance declaration at Read.hs:4:10-32<br>
    The type variable ‘t0’ is ambiguous<br>
    Relevant bindings include<br>
      readsPrec :: Int -> ReadS (List a) (bound at Read.hs:5:3)<br>
    Note: there are several potential instances:<br>
      instance (Read a, Read b) => Read (Either a b)<br>
        -- Defined in ‘Data.Either’<br>
      instance forall (k :: BOX) (s :: k). Read (Data.Proxy.Proxy s)<br>
        -- Defined in ‘Data.Proxy’<br>
      instance (GHC.Arr.Ix a, Read a, Read b) => Read (GHC.Arr.Array a b)<br>
        -- Defined in ‘GHC.Read’<br>
      ...plus 18 others<br>
    In the second argument of ‘map’, namely ‘(readsPrec d s)’<br>
    In the expression: map convert (readsPrec d s)<br>
    In an equation for ‘readsPrec’:<br>
        readsPrec d s<br>
          = map convert (readsPrec d s)<br>
          where<br>
              convert (xs, s2) = (foldr Cons Nil xs, s2)<br>
~~~<br>
<br>
The reason is the usage of foldr, which changed its type from<br>
<br>
  foldr :: (a -> b -> b) -> b -> [a] -> b -- GHC 7.8.4<br>
<br>
to<br>
<br>
  foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b -- GHC 7.10.1<br>
<br>
Thus, the use of foldr is now ambiguous. I can fix this by providing a<br>
type signature<br>
<br>
  convert :: ([a], String) -> (List a, String)<br>
<br>
However, is this breaking change intended?<br>
<br>
Regards,<br>
Björn<br>
<br>
<br>
<br>
<br>
_______________________________________________<br>
Glasgow-haskell-users mailing list<br>
<a href="mailto:Glasgow-haskell-users@haskell.org">Glasgow-haskell-users@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/glasgow-haskell-users" target="_blank">http://www.haskell.org/mailman/listinfo/glasgow-haskell-users</a><br>
</blockquote></div><br></div>