
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

On 20 Jan 2015, at 11:20, Björn Peemöller wrote:
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?
I believe this kind of breakage was predicted by those opposed to the change of signature. That is not quite the same thing as being intended or desired. Regards, Malcolm

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

On Tue, Jan 20, 2015 at 6:45 PM, Edward Kmett
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.
There are few reports because the change hasn't affected the dark majority yet. RC builds are used by a tiny fraction. There's a long tail of users still on 7.6, 7.4, 7.2, and 6.x. The whack-a-mole game needs only to be played once and the results shared among those relying on the abstractions. Was that route ever explored? The FTP discussion needs to be re-opened. And it will be, eventually. -- Kim-Ee

On Tue, Jan 20, 2015 at 9:00 AM, Kim-Ee Yeoh
There are few reports because the change hasn't affected the dark majority yet. RC builds are used by a tiny fraction. There's a long tail of users still on 7.6, 7.4, 7.2, and 6.x.
We've been actively testing since the first time we had a usable implementation of both the Foldable/Traversable proposal and AMP. Very large chunks of hackage have been built in house with hand-patched upstreams to maximize how much of it we can build and we've been using that to try to minimize impact. Herbert has been hard at work on this for six months now. It was known going in that there'd be some broken eggs, and that there'd be a large number of details to figure out, so Simon formed the core libraries committee in part to have someone responsible for making decisions around situations like this. Far and away the greatest contributing factor to build failures in 7.10 is the AMP. More code is broken by the import of (<*>) in Applicative alone. As in, going into the same release, the Foldable/Traversable changes barely blip the build-failure radar, by a factor of 50 compared to AMP-induced failures. The whack-a-mole game needs only to be played once and the results shared
among those relying on the abstractions. Was that route ever explored?
Yes. You could say that this is precisely what we've been doing since 2008. We've had a dozen or so alternate preludes. Nobody wants the extra build dependency or per module setup cost. We've had a proposal to eliminate the Prelude entirely by Igloo, to make it so if you import Prelude.Foo you'd get that Prelude and not the other. I also spent much of 2014 going around to every Haskell meetup I could make it to around the world looking for more direct feedback from folks. The list goes on of options that have been put on the table. It does nothing to stem the tide of users who reinvent these abstractions, or who by dint of the undiscoverability of the current API never find out about it. The classy-prelude for instance when it was first released didn't know that there was any pre-existing relationship between virtually all the combinators it offered and split things up into dozens of classes. A separate Prelude doesn't address the fact that the limited versions of these functions are re-exported over and over across dozens of other modules within base and without. To that end we had a proposal. It had the most feedback of any proposal ever put forth on the libraries mailing list, but it went through with something like 90% approval. I'm not one to speak of "mandates from the people", but if anything ever came close, that sounds like one to me. The FTP discussion needs to be re-opened. And it will be, eventually.
That statement needs some seriously sinister music. ;) -Edward

On Tue, Jan 20, 2015 at 3:45 AM, Edward Kmett
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.
For the record, it took me almost an hour to update attoparsec to fix all the various regressions, or to put it more charitably changes, introduced in GHC 7.10. I have twenty-something other packages to go through. I don't keep track of the time sunk from release to release, but this feels somewhat worse than average. Basically, the more careful you are in writing a package, the more each update of GHC and base costs in nickel-and-dime tweaks to keep a build clean. It's not a very happy-making feedback loop. "Be a good citizen, and your reward is to spend *even more* time cleaning up!"

Hello Bryan, On 2015-01-20 at 23:17:01 +0100, Bryan O'Sullivan wrote: [...]
For the record, it took me almost an hour to update attoparsec to fix all the various regressions, or to put it more charitably changes, introduced in GHC 7.10. I have twenty-something other packages to go through. I don't keep track of the time sunk from release to release, but this feels somewhat worse than average.
I'm a bit confused, several past attoparsec versions seem to build just fine with GHC 7.10: https://ghc.haskell.org/~hvr/buildreports/attoparsec.html were there hidden breakages not resulting in compile errors? Or are the fixes you mention about restoring -Wall hygiene?
Basically, the more careful you are in writing a package, the more each update of GHC and base costs in nickel-and-dime tweaks to keep a build clean. It's not a very happy-making feedback loop. "Be a good citizen, and your reward is to spend *even more* time cleaning up!"
Cheers, hvr

On Tue, Jan 20, 2015 at 3:02 PM, Herbert Valerio Riedel
I'm a bit confused, several past attoparsec versions seem to build just fine with GHC 7.10:
https://ghc.haskell.org/~hvr/buildreports/attoparsec.html
were there hidden breakages not resulting in compile errors? Or are the fixes you mention about restoring -Wall hygiene?
I build with -Wall -Werror, and also have to maintain the test and benchmark suites.

Building -Wall clean across this change-over has a big of a trick to it.
The easiest way I know of when folks already had lots of
import Data.Foldable
import Data.Traversable
stuff
is to just add
import Prelude
explicitly to the bottom of your import list rather than painstakingly
exclude the imports with CPP.
This has the benefit of not needing a bunch of CPP to manage what names
come from where.
Why? GHC checks that the imports provide something 'new' that is used by
the module in a top-down fashion, and you are almost suredly using
something from Prelude that didn't come from one of the modules above.
On the other hand the implicit import of Prelude effectively would come
first in the list.
It is a dirty trick, but it does neatly side-step this problem for folks in
your situation.
-Edward
On Tue, Jan 20, 2015 at 6:12 PM, Bryan O'Sullivan
On Tue, Jan 20, 2015 at 3:02 PM, Herbert Valerio Riedel
wrote: I'm a bit confused, several past attoparsec versions seem to build just fine with GHC 7.10:
https://ghc.haskell.org/~hvr/buildreports/attoparsec.html
were there hidden breakages not resulting in compile errors? Or are the fixes you mention about restoring -Wall hygiene?
I build with -Wall -Werror, and also have to maintain the test and benchmark suites.

Hello Edward, Shouldn't we publicize this trick? Perhaps in the changelog? Edward Excerpts from Edward Kmett's message of 2015-01-20 15:22:57 -0800:
Building -Wall clean across this change-over has a big of a trick to it.
The easiest way I know of when folks already had lots of
import Data.Foldable import Data.Traversable
stuff
is to just add
import Prelude
explicitly to the bottom of your import list rather than painstakingly exclude the imports with CPP.
This has the benefit of not needing a bunch of CPP to manage what names come from where.
Why? GHC checks that the imports provide something 'new' that is used by the module in a top-down fashion, and you are almost suredly using something from Prelude that didn't come from one of the modules above.
On the other hand the implicit import of Prelude effectively would come first in the list.
It is a dirty trick, but it does neatly side-step this problem for folks in your situation.
-Edward
On Tue, Jan 20, 2015 at 6:12 PM, Bryan O'Sullivan
wrote: On Tue, Jan 20, 2015 at 3:02 PM, Herbert Valerio Riedel
wrote: I'm a bit confused, several past attoparsec versions seem to build just fine with GHC 7.10:
https://ghc.haskell.org/~hvr/buildreports/attoparsec.html
were there hidden breakages not resulting in compile errors? Or are the fixes you mention about restoring -Wall hygiene?
I build with -Wall -Werror, and also have to maintain the test and benchmark suites.

Sure.
Adding it to the CHANGELOG makes a lot of sense. I first found out about it
only a few weeks ago when Herbert mentioned it in passing.
Of course, the geek in me definitely prefers technical fixes to human ones.
Humans are messy. =)
I'd be curious how much of the current suite of warnings could be fixed
just by switching the implicit Prelude import to the end of the import list
inside GHC.
Now that Herbert has all of his crazy tooling to build stuff with 7.10 and
with HEAD, it might be worth trying out such a change to see how much it
reduces the warning volume and if it somehow manages to introduce any new
warnings.
I hesitate to make such a proposal this late in the release candidate game,
but if it worked it'd be pretty damn compelling.
-Edward
On Tue, Jan 20, 2015 at 6:27 PM, Edward Z. Yang
Hello Edward,
Shouldn't we publicize this trick? Perhaps in the changelog?
Edward
Excerpts from Edward Kmett's message of 2015-01-20 15:22:57 -0800:
Building -Wall clean across this change-over has a big of a trick to it.
The easiest way I know of when folks already had lots of
import Data.Foldable import Data.Traversable
stuff
is to just add
import Prelude
explicitly to the bottom of your import list rather than painstakingly exclude the imports with CPP.
This has the benefit of not needing a bunch of CPP to manage what names come from where.
Why? GHC checks that the imports provide something 'new' that is used by the module in a top-down fashion, and you are almost suredly using something from Prelude that didn't come from one of the modules above.
On the other hand the implicit import of Prelude effectively would come first in the list.
It is a dirty trick, but it does neatly side-step this problem for folks in your situation.
-Edward
On Tue, Jan 20, 2015 at 6:12 PM, Bryan O'Sullivan
wrote: On Tue, Jan 20, 2015 at 3:02 PM, Herbert Valerio Riedel
wrote: I'm a bit confused, several past attoparsec versions seem to build
just
fine with GHC 7.10:
https://ghc.haskell.org/~hvr/buildreports/attoparsec.html
were there hidden breakages not resulting in compile errors? Or are the fixes you mention about restoring -Wall hygiene?
I build with -Wall -Werror, and also have to maintain the test and benchmark suites.

I like this proposal: if you're explicit about an import that would otherwise be implicit by Prelude, you shouldn't get a warning for it. If it is not already the case, we also need to make sure the implicit Prelude import never causes "unused import" errors. Edward Excerpts from Edward Kmett's message of 2015-01-20 15:41:13 -0800:
Sure.
Adding it to the CHANGELOG makes a lot of sense. I first found out about it only a few weeks ago when Herbert mentioned it in passing.
Of course, the geek in me definitely prefers technical fixes to human ones. Humans are messy. =)
I'd be curious how much of the current suite of warnings could be fixed just by switching the implicit Prelude import to the end of the import list inside GHC.
Now that Herbert has all of his crazy tooling to build stuff with 7.10 and with HEAD, it might be worth trying out such a change to see how much it reduces the warning volume and if it somehow manages to introduce any new warnings.
I hesitate to make such a proposal this late in the release candidate game, but if it worked it'd be pretty damn compelling.
-Edward
On Tue, Jan 20, 2015 at 6:27 PM, Edward Z. Yang
wrote: Hello Edward,
Shouldn't we publicize this trick? Perhaps in the changelog?
Edward
Excerpts from Edward Kmett's message of 2015-01-20 15:22:57 -0800:
Building -Wall clean across this change-over has a big of a trick to it.
The easiest way I know of when folks already had lots of
import Data.Foldable import Data.Traversable
stuff
is to just add
import Prelude
explicitly to the bottom of your import list rather than painstakingly exclude the imports with CPP.
This has the benefit of not needing a bunch of CPP to manage what names come from where.
Why? GHC checks that the imports provide something 'new' that is used by the module in a top-down fashion, and you are almost suredly using something from Prelude that didn't come from one of the modules above.
On the other hand the implicit import of Prelude effectively would come first in the list.
It is a dirty trick, but it does neatly side-step this problem for folks in your situation.
-Edward
On Tue, Jan 20, 2015 at 6:12 PM, Bryan O'Sullivan
wrote: On Tue, Jan 20, 2015 at 3:02 PM, Herbert Valerio Riedel
wrote: I'm a bit confused, several past attoparsec versions seem to build
just
fine with GHC 7.10:
https://ghc.haskell.org/~hvr/buildreports/attoparsec.html
were there hidden breakages not resulting in compile errors? Or are the fixes you mention about restoring -Wall hygiene?
I build with -Wall -Werror, and also have to maintain the test and benchmark suites.

It isn't without a cost. On the down-side, the results of
-ddump-minimal-imports would be er.. less minimal.
On Tue, Jan 20, 2015 at 6:47 PM, Edward Z. Yang
I like this proposal: if you're explicit about an import that would otherwise be implicit by Prelude, you shouldn't get a warning for it. If it is not already the case, we also need to make sure the implicit Prelude import never causes "unused import" errors.
Edward
Sure.
Adding it to the CHANGELOG makes a lot of sense. I first found out about it only a few weeks ago when Herbert mentioned it in passing.
Of course, the geek in me definitely prefers technical fixes to human ones. Humans are messy. =)
I'd be curious how much of the current suite of warnings could be fixed just by switching the implicit Prelude import to the end of the import
inside GHC.
Now that Herbert has all of his crazy tooling to build stuff with 7.10 and with HEAD, it might be worth trying out such a change to see how much it reduces the warning volume and if it somehow manages to introduce any new warnings.
I hesitate to make such a proposal this late in the release candidate game, but if it worked it'd be pretty damn compelling.
-Edward
On Tue, Jan 20, 2015 at 6:27 PM, Edward Z. Yang
wrote: Hello Edward,
Shouldn't we publicize this trick? Perhaps in the changelog?
Edward
Excerpts from Edward Kmett's message of 2015-01-20 15:22:57 -0800:
Building -Wall clean across this change-over has a big of a trick to it.
The easiest way I know of when folks already had lots of
import Data.Foldable import Data.Traversable
stuff
is to just add
import Prelude
explicitly to the bottom of your import list rather than
Excerpts from Edward Kmett's message of 2015-01-20 15:41:13 -0800: list painstakingly
exclude the imports with CPP.
This has the benefit of not needing a bunch of CPP to manage what names come from where.
Why? GHC checks that the imports provide something 'new' that is used by the module in a top-down fashion, and you are almost suredly using something from Prelude that didn't come from one of the modules above.
On the other hand the implicit import of Prelude effectively would come first in the list.
It is a dirty trick, but it does neatly side-step this problem for folks in your situation.
-Edward
On Tue, Jan 20, 2015 at 6:12 PM, Bryan O'Sullivan < bos@serpentine.com> wrote:
On Tue, Jan 20, 2015 at 3:02 PM, Herbert Valerio Riedel <
hvr@gnu.org>
wrote:
I'm a bit confused, several past attoparsec versions seem to build just fine with GHC 7.10:
https://ghc.haskell.org/~hvr/buildreports/attoparsec.html
were there hidden breakages not resulting in compile errors? Or are the fixes you mention about restoring -Wall hygiene?
I build with -Wall -Werror, and also have to maintain the test and benchmark suites.

I don't see why that would be the case: we haven't *excluded* any old import lists, so -ddump-minimal-imports could still take advantage of Prelude in a warning-free way. Edward Excerpts from Edward Kmett's message of 2015-01-20 16:36:53 -0800:
It isn't without a cost. On the down-side, the results of -ddump-minimal-imports would be er.. less minimal.
On Tue, Jan 20, 2015 at 6:47 PM, Edward Z. Yang
wrote: I like this proposal: if you're explicit about an import that would otherwise be implicit by Prelude, you shouldn't get a warning for it. If it is not already the case, we also need to make sure the implicit Prelude import never causes "unused import" errors.
Edward
Sure.
Adding it to the CHANGELOG makes a lot of sense. I first found out about it only a few weeks ago when Herbert mentioned it in passing.
Of course, the geek in me definitely prefers technical fixes to human ones. Humans are messy. =)
I'd be curious how much of the current suite of warnings could be fixed just by switching the implicit Prelude import to the end of the import
inside GHC.
Now that Herbert has all of his crazy tooling to build stuff with 7.10 and with HEAD, it might be worth trying out such a change to see how much it reduces the warning volume and if it somehow manages to introduce any new warnings.
I hesitate to make such a proposal this late in the release candidate game, but if it worked it'd be pretty damn compelling.
-Edward
On Tue, Jan 20, 2015 at 6:27 PM, Edward Z. Yang
wrote: Hello Edward,
Shouldn't we publicize this trick? Perhaps in the changelog?
Edward
Excerpts from Edward Kmett's message of 2015-01-20 15:22:57 -0800:
Building -Wall clean across this change-over has a big of a trick to it.
The easiest way I know of when folks already had lots of
import Data.Foldable import Data.Traversable
stuff
is to just add
import Prelude
explicitly to the bottom of your import list rather than
Excerpts from Edward Kmett's message of 2015-01-20 15:41:13 -0800: list painstakingly
exclude the imports with CPP.
This has the benefit of not needing a bunch of CPP to manage what names come from where.
Why? GHC checks that the imports provide something 'new' that is used by the module in a top-down fashion, and you are almost suredly using something from Prelude that didn't come from one of the modules above.
On the other hand the implicit import of Prelude effectively would come first in the list.
It is a dirty trick, but it does neatly side-step this problem for folks in your situation.
-Edward
On Tue, Jan 20, 2015 at 6:12 PM, Bryan O'Sullivan < bos@serpentine.com> wrote:
On Tue, Jan 20, 2015 at 3:02 PM, Herbert Valerio Riedel <
hvr@gnu.org>
wrote:
> I'm a bit confused, several past attoparsec versions seem to build just > fine with GHC 7.10: > > https://ghc.haskell.org/~hvr/buildreports/attoparsec.html > > were there hidden breakages not resulting in compile errors? > Or are the fixes you mention about restoring -Wall hygiene? >
I build with -Wall -Werror, and also have to maintain the test and benchmark suites.

I was assuming that the list was generated by doing more or less the same
check we do now. I haven't looked at the code for it.
If so, then it seems it wouldn't flag a now-unnecessary Data.Traversable
dependency for instance. At least not without rather significant retooling.
I might be off in my understanding of how it works, though.
-Edward
On Tue, Jan 20, 2015 at 7:40 PM, Edward Z. Yang
I don't see why that would be the case: we haven't *excluded* any old import lists, so -ddump-minimal-imports could still take advantage of Prelude in a warning-free way.
Edward
It isn't without a cost. On the down-side, the results of -ddump-minimal-imports would be er.. less minimal.
On Tue, Jan 20, 2015 at 6:47 PM, Edward Z. Yang
wrote: I like this proposal: if you're explicit about an import that would otherwise be implicit by Prelude, you shouldn't get a warning for it. If it is not already the case, we also need to make sure the implicit Prelude import never causes "unused import" errors.
Edward
Sure.
Adding it to the CHANGELOG makes a lot of sense. I first found out about it only a few weeks ago when Herbert mentioned it in passing.
Of course, the geek in me definitely prefers technical fixes to human ones. Humans are messy. =)
I'd be curious how much of the current suite of warnings could be fixed just by switching the implicit Prelude import to the end of the import
Excerpts from Edward Kmett's message of 2015-01-20 15:41:13 -0800: list
inside GHC.
Now that Herbert has all of his crazy tooling to build stuff with 7.10 and with HEAD, it might be worth trying out such a change to see how much it reduces the warning volume and if it somehow manages to introduce any new warnings.
I hesitate to make such a proposal this late in the release candidate game, but if it worked it'd be pretty damn compelling.
-Edward
On Tue, Jan 20, 2015 at 6:27 PM, Edward Z. Yang
wrote: Hello Edward,
Shouldn't we publicize this trick? Perhaps in the changelog?
Edward
Excerpts from Edward Kmett's message of 2015-01-20 15:22:57 -0800:
Building -Wall clean across this change-over has a big of a
Excerpts from Edward Kmett's message of 2015-01-20 16:36:53 -0800: trick to
The easiest way I know of when folks already had lots of
import Data.Foldable import Data.Traversable
stuff
is to just add
import Prelude
explicitly to the bottom of your import list rather than
it. painstakingly
exclude the imports with CPP.
This has the benefit of not needing a bunch of CPP to manage what names come from where.
Why? GHC checks that the imports provide something 'new' that is used by the module in a top-down fashion, and you are almost suredly using something from Prelude that didn't come from one of the modules above.
On the other hand the implicit import of Prelude effectively would come first in the list.
It is a dirty trick, but it does neatly side-step this problem for folks in your situation.
-Edward
On Tue, Jan 20, 2015 at 6:12 PM, Bryan O'Sullivan < bos@serpentine.com> wrote:
> > On Tue, Jan 20, 2015 at 3:02 PM, Herbert Valerio Riedel < hvr@gnu.org> > wrote: > >> I'm a bit confused, several past attoparsec versions seem to build just >> fine with GHC 7.10: >> >> https://ghc.haskell.org/~hvr/buildreports/attoparsec.html >> >> were there hidden breakages not resulting in compile errors? >> Or are the fixes you mention about restoring -Wall hygiene? >> > > I build with -Wall -Werror, and also have to maintain the test and > benchmark suites. >

On 2015-01-21 at 00:27:39 +0100, Edward Z. Yang wrote:
Hello Edward,
Shouldn't we publicize this trick? Perhaps in the changelog?
Fwiw, I've added that workaround/recipe to https://ghc.haskell.org/trac/ghc/wiki/Migration/7.10#GHCsaysTheimportof...is... feel free to improve the wording... :-)
participants (7)
-
Björn Peemöller
-
Bryan O'Sullivan
-
Edward Kmett
-
Edward Z. Yang
-
Herbert Valerio Riedel
-
Kim-Ee Yeoh
-
Malcolm Wallace