Warning when deriving Foldable/Traversable using -Wall

I am not sure how to report bugs against the current development version of GHC. Should this go into Trac? The current HEAD gives a spurious unused declaration when deriving Typable/Traversable Details Compiling against current HEAD (0ed9a2779a2adf0347088134fdb9f60ae9f2735b) Adding test('T9069w', extra_clean(['T9069.o', 'T9069.hi']), multimod_compile, ['T9069', '-Wall']) to testsuite/tests/deriving/should_compile/all.T results in +[1 of 1] Compiling T9069 ( T9069.hs, T9069.o ) + +T9069.hs:5:1: Warning: + The import of ‘Data.Foldable’ is redundant + except perhaps to import instances from ‘Data.Foldable’ + To import instances alone, use: import Data.Foldable() + +T9069.hs:6:1: Warning: + The import of ‘Data.Traversable’ is redundant + except perhaps to import instances from ‘Data.Traversable’ + To import instances alone, use: import Data.Traversable() *** unexpected failure for T9069w(optasm) The file being compiled is -------------------------------------------- {-# LANGUAGE DeriveTraversable #-} module T9069 where import Data.Foldable import Data.Traversable data Trivial a = Trivial a deriving (Functor,Foldable,Traversable) ---------------------------------------------

On 2014-10-08 at 14:00:05 +0200, Alan & Kim Zimmerman wrote: [...]
Should this go into Trac?
Fwiw, there is a version "7.9" you can select when writing a Trac ticket for the very purpose to file bugs against GHC HEAD. [...]
The file being compiled is
-------------------------------------------- {-# LANGUAGE DeriveTraversable #-}
module T9069 where
import Data.Foldable import Data.Traversable
data Trivial a = Trivial a deriving (Functor,Foldable,Traversable) ---------------------------------------------
There's two simple ways to workaround this; either a) add a 'import Prelude' after the two imports or b) remove the two imports The a) option has the benefit that it will still work with GHC 7.8.3

On Wed, 2014-10-08 at 14:00 +0200, Alan & Kim Zimmerman wrote:
The current HEAD gives a spurious unused declaration when deriving Typable/Traversable
Why would this be spurious, given `Foldable` and `Traversable` are now exported by `Prelude`, so those imports are in fact not necessary? Nicolas

Ok, so stage2 is in fact behaving correctly, the stage1 code needs to have
CPP directives around it.
In other words this is not actually a bug.
Thanks
Alan
On Wed, Oct 8, 2014 at 2:05 PM, Nicolas Trangez
On Wed, 2014-10-08 at 14:00 +0200, Alan & Kim Zimmerman wrote:
The current HEAD gives a spurious unused declaration when deriving Typable/Traversable
Why would this be spurious, given `Foldable` and `Traversable` are now exported by `Prelude`, so those imports are in fact not necessary?
Nicolas

Yes, please add as a Trac ticket! thank you Simon From: ghc-devs [mailto:ghc-devs-bounces@haskell.org] On Behalf Of Alan & Kim Zimmerman Sent: 08 October 2014 13:00 To: ghc-devs@haskell.org Subject: Warning when deriving Foldable/Traversable using -Wall I am not sure how to report bugs against the current development version of GHC. Should this go into Trac? The current HEAD gives a spurious unused declaration when deriving Typable/Traversable Details Compiling against current HEAD (0ed9a2779a2adf0347088134fdb9f60ae9f2735b) Adding test('T9069w', extra_clean(['T9069.o', 'T9069.hi']), multimod_compile, ['T9069', '-Wall']) to testsuite/tests/deriving/should_compile/all.T results in +[1 of 1] Compiling T9069 ( T9069.hs, T9069.o ) + +T9069.hs:5:1: Warning: + The import of ‘Data.Foldable’ is redundant + except perhaps to import instances from ‘Data.Foldable’ + To import instances alone, use: import Data.Foldable() + +T9069.hs:6:1: Warning: + The import of ‘Data.Traversable’ is redundant + except perhaps to import instances from ‘Data.Traversable’ + To import instances alone, use: import Data.Traversable() *** unexpected failure for T9069w(optasm) The file being compiled is -------------------------------------------- {-# LANGUAGE DeriveTraversable #-} module T9069 where import Data.Foldable import Data.Traversable data Trivial a = Trivial a deriving (Functor,Foldable,Traversable) ---------------------------------------------
participants (4)
-
Alan & Kim Zimmerman
-
Herbert Valerio Riedel
-
Nicolas Trangez
-
Simon Peyton Jones