[GHC] #11719: Cannot use higher-rank kinds with type families
GHC
ghc-devs at haskell.org
Wed Oct 10 17:19:58 UTC 2018
#11719: Cannot use higher-rank kinds with type families
-------------------------------------+-------------------------------------
Reporter: ocharles | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.8.1
Component: Compiler (Type | Version: 8.0.1-rc2
checker) |
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC rejects | Test Case:
valid program | dependent/should_compile/T11719
Blocked By: | Blocking:
Related Tickets: #13913 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Is this another consequence of this limitation? Consider the following
program:
{{{#!hs
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Bug where
import Data.Kind
type family Sing :: k -> Type
data SBool :: Bool -> Type where
SFalse :: SBool False
STrue :: SBool True
type instance Sing = SBool
sFalse :: Sing False
sFalse = SFalse
}}}
This typechecks without issue. However, if you change the following line
of code:
{{{#!hs
type family Sing :: k -> Type
}}}
To become this:
{{{#!hs
type family Sing :: forall k. k -> Type
}}}
Then it stops typechecking:
{{{
$ /opt/ghc/8.6.1/bin/ghc Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
Bug.hs:18:10: error:
• Couldn't match type ‘SBool’ with ‘Sing’
Expected type: Sing 'False
Actual type: SBool 'False
• In the expression: SFalse
In an equation for ‘sFalse’: sFalse = SFalse
|
18 | sFalse = SFalse
| ^^^^^^
}}}
I find this extremely surprising: I would have thought that GHC could
treat `type family Sing :: k -> Type` and `type family Sing :: forall k. k
-> Type` identically without the need for any fancy higher-rank business
(like what the original program in this ticket requires).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11719#comment:13>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list