[GHC] #13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in 8.2
GHC
ghc-devs at haskell.org
Thu Apr 20 02:06:43 UTC 2017
#13594: Typechecker behavior w.r.t. BangPatterns and nested foralls has changed in
8.2
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1-rc2
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Try running this code in GHCi:
{{{
λ> :set -XBangPatterns -XRankNTypes -XTypeFamilies
λ> let x :: forall a . a ~ Integer => forall b. b ~ Integer => (a, b); !x
= (1, 2)
}}}
In GHC 8.0.1 and 8.0.2, this works. But in GHC 8.2.1:
{{{
<interactive>:3:74:
Couldn't match expected type ‘forall a.
(a ~ Integer) =>
forall b. (b ~ Integer) => (a, b)’
with actual type ‘(Integer, Integer)’
In the expression: (1, 2)
In a pattern binding: !x = (1, 2)
}}}
If you put this code into a source file:
{{{#!hs
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
module Bug where
x :: forall a . a ~ Integer => forall b. b ~ Integer => (a, b)
!x = (1, 2)
}}}
Then it also works in GHC 8.0.1. and 8.0.2, but it errors on GHC 8.2 (this
time with a different error):
{{{
GHCi, version 8.2.0.20170413: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Bug.hs:6:1: error:
Overloaded signature conflicts with monomorphism restriction
x :: forall a. a ~ Integer => forall b. b ~ Integer => (a, b)
|
6 | x :: forall a . a ~ Integer => forall b. b ~ Integer => (a, b)
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13594>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list