[GHC] #12922: Kind classes compile with PolyKinds
GHC
ghc-devs at haskell.org
Sun Dec 4 01:05:51 UTC 2016
#12922: Kind classes compile with PolyKinds
-------------------------------------+-------------------------------------
Reporter: Tritlo | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by Tritlo:
@@ -20,0 +20,1 @@
+ type (S a) + b = S (a + b)
New description:
I was asking around on #haskell to better understand the new language
extension, -XTypeInType, and how it is different from -XPolyKinds.
To study it, I was working with the following small example:
{{{
{-# LANGUAGE TypeFamilies, GADTs, TypeOperators, DataKinds, PolyKinds #-}
module Main where
import Data.Kind (Type)
-- Define a Type for the natural numbers, Zero and a successor
data Nat = Z | S Nat
class Addable k where
type (a :: k) + (b :: k) :: k
instance Addable Nat where
type (Z + a) = a
type (S a) + b = S (a + b)
}}}
(for more context, see
https://gist.github.com/Tritlo/ce5510e80935ac398a33934ee47c7930)
Since according to a responder on #haskell, the ability to have kind
classes required TypeInType, and should not work with PolyKinds.
As the documentation mentions that there could be leakage between
PolyKinds and TypeInType and to report such leaks, I felt that I should
report it.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12922#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list