[GHC] #12922: Kind classes compile with PolyKinds

GHC ghc-devs at haskell.org
Mon Dec 5 01:49:21 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:

@@ -7,1 +7,1 @@
- {-# LANGUAGE TypeFamilies, GADTs, TypeOperators, DataKinds, PolyKinds #-}
+ {-# LANGUAGE TypeFamilies, TypeOperators, DataKinds, PolyKinds #-}
@@ -10,3 +10,1 @@
- import Data.Kind (Type)
-
- -- Define a Type for the natural numbers, Zero and a successor
+ -- Define a Type for the natural numbers, zero and a successor
@@ -21,0 +19,3 @@
+
+ main :: IO ()
+ main = putStrLn "Shouldn't this need TypeInType?"

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, TypeOperators, DataKinds, PolyKinds #-}
 module Main where

 -- 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)

 main :: IO ()
 main = putStrLn "Shouldn't this need TypeInType?"
 }}}

 (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:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list