[GHC] #9981: Potential typechecker regression in GHC 7.10.1RC
GHC
ghc-devs at haskell.org
Tue Jan 13 18:15:25 UTC 2015
#9981: Potential typechecker regression in GHC 7.10.1RC
-------------------------------------+-------------------------------------
Reporter: hvr | Owner: simonpj
Type: bug | Status: new
Priority: highest | Milestone: 7.10.1
Component: Compiler | Version: 7.10.1-rc1
(Type checker) | Operating System: Unknown/Multiple
Keywords: | Type of failure: GHC rejects
Architecture: | valid program
Unknown/Multiple | Blocked By:
Test Case: | Related Tickets:
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
The following snippet (extracted from hackage:index-core) is accepted by
GHCs prior to GHC 7.10:
{{{#!hs
{-# LANGUAGE Rank2Types, TypeOperators #-}
module Foo where
type a :-> b = forall i . a i -> b i
class IFunctor f where
fmapI :: (a :-> b) -> (f a :-> f b)
class (IFunctor m) => IMonad m where
returnI :: a :-> m a
bindI :: (a :-> m b) -> (m a :-> m b)
(?>=) :: (IMonad m) => m a i -> (a :-> m b) -> m b i
(?>=) = flip bindI
}}}
{{{
$ ghci-7.8.4 -Wall Foo.hs
GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Control.IMonad.Core ( Foo.hs, interpreted )
Ok, modules loaded: Control.IMonad.Core.
λ:2> :browse
type (:->) (a :: * -> *) (b :: * -> *) = forall i. a i -> b i
class IFunctor (f :: (* -> *) -> * -> *) where
fmapI :: (a :-> b) -> f a :-> f b
class IFunctor m => IMonad (m :: (* -> *) -> * -> *) where
returnI :: a i -> m a i
bindI :: (a :-> m b) -> m a :-> m b
(?>=) :: IMonad m => m a i -> (a :-> m b) -> m b i
}}}
vs.
{{{
$ ghci-7.10.0.20141227 -Wall Foo.hs
GHCi, version 7.10.0.20141227: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Control.IMonad.Core ( Foo.hs, interpreted )
Foo.hs:15:14:
Couldn't match type ‘a i0 -> m b i0’ with ‘forall i1. a i1 -> m b i1’
Expected type: (a i0 -> m b i0) -> m a i -> m b i
Actual type: a :-> m b -> m a i -> m b i
Relevant bindings include (?>=) :: m a i -> a :-> m b -> m b i (bound
at Foo.hs:15:1)
In the first argument of ‘flip’, namely ‘bindI’
In the expression: flip bindI
Failed, modules loaded: none.
λ:2>
}}}
I'm not sure though whether that module was valid to begin with...
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9981>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list