[GHC] #11319: ImpredicativeTypes cause trouble (affects deriving of Traversable)
GHC
ghc-devs at haskell.org
Wed Dec 30 23:30:45 UTC 2015
#11319: ImpredicativeTypes cause trouble (affects deriving of Traversable)
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
(Type checker) |
Keywords: | Operating System: Linux
ImpredicativeTypes |
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I don't have the latest version of GHC, trying to derive `Functor A` and
`Foldable A` is fine but when I derive `Traversable A` in the attachment
Error.hs:
{{{#!hs
{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable,
ImpredicativeTypes #-}
import Data.Functor (Functor)
import Data.Foldable (Foldable)
import Data.Traversable (Traversable)
data A a = A
deriving (Functor, Foldable, Traversable)
}}}
GHC barks at me (verbose log attached):
{{{#!hs
/tmp/Error.hs:8:32: error:
• Couldn't match type ‘forall a1. A a1’ with ‘A b’
Expected type: f (A b)
Actual type: f (forall a. A a)
• In the expression: pure A
In an equation for ‘traverse’: traverse f A = pure A
When typechecking the code for ‘traverse’
in a derived instance for ‘Traversable A’:
To see the code I am typechecking, use -ddump-deriv
In the instance declaration for ‘Traversable A’
• Relevant bindings include
f :: a -> f b (bound at /tmp/Error.hs:8:32)
traverse :: (a -> f b) -> A a -> f (A b)
(bound at /tmp/Error.hs:8:32)
}}}
With `-ddump-deriv` we get this (unqualified) instance:
{{{#!hs
instance Traversable A where
traverse f_a2Le A = pure A
}}}
which by itself causes the same problem in the attachment Error2.hs:
{{{#!hs
{-# LANGUAGE DeriveFunctor, DeriveFoldable, ImpredicativeTypes #-}
import Data.Functor (Functor)
import Data.Foldable (Foldable)
import Data.Traversable (Traversable)
data A a = A
deriving (Functor, Foldable)
instance Traversable A where
traverse f A = pure A
}}}
Works fine in GHC-7.10.2 and GHC-7.10.0.20150316 and GHC-7.4 (with some
additional imports), is this an `ImpredicativeTypes` regression?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11319>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list