Warning when deriving Foldable/Traversable using -Wall
Simon Peyton Jones
simonpj at microsoft.com
Wed Oct 8 12:07:14 UTC 2014
Yes, please add as a Trac ticket! thank you
Simon
From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Alan & Kim Zimmerman
Sent: 08 October 2014 13:00
To: ghc-devs at 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)
---------------------------------------------
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/ghc-devs/attachments/20141008/7557d4fc/attachment.html>
More information about the ghc-devs
mailing list