[GHC] #14121: ghc master requires -XTypeInType where 8.2.1 does not
GHC
ghc-devs at haskell.org
Tue Aug 15 22:25:42 UTC 2017
#14121: ghc master requires -XTypeInType where 8.2.1 does not
-------------------------------------+-------------------------------------
Reporter: duog | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.3
(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:
-------------------------------------+-------------------------------------
This was found while building
https://hackage.haskell.org/package/foundation with ghc head.
The following code is reduced from Basement.Primitive.Error:
{{{
{-# LANGUAGE MagicHash, PolyKinds, RankNTypes #-}
module FoundationRegression where
import GHC.Prim
import GHC.Types (RuntimeRep)
error :: forall (r :: RuntimeRep) . forall (a :: TYPE r) . String -> a
error s = raise# undefined
}}}
This compiles works with 8.2.1, but fails on master:
{{{
$ /opt/ghc/8.2.1/bin/ghc -c FoundationRegression.hs
$ /opt/ghc/head/bin/ghc -c FoundationRegression.hs
FoundationRegression.hs:7:17: error:
Variable ‘r’ used as both a kind and a type
Did you intend to use TypeInType?
|
7 | error :: forall (r :: RuntimeRep) . forall (a :: TYPE r) . String -> a
| ^^^^^^^^^^^^^^^^^
}}}
After adding a TypeInType language pragma the program is accepted.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14121>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list