Kinds of type synonym arguments
Ömer Sinan Ağacan
omeragacan at gmail.com
Sun Dec 6 18:55:56 UTC 2015
In this program:
{-# LANGUAGE MagicHash, UnboxedTuples #-}
module Main where
import GHC.Prim
import GHC.Types
type Tuple a b = (# a, b #)
main = do
let -- x :: Tuple Int# Float#
x :: (# Int#, Float# #)
x = (# 1#, 0.0# #)
return ()
If I use the first type declaration for 'x' I'm getting this error message:
Expecting a lifted type, but ‘Int#’ is unlifted
Indeed, if I look at the kinds of arguments of 'Tuple':
λ:7> :k Tuple
Tuple :: * -> * -> #
It's star. I was wondering why is this not 'OpenKind'(or whatever the
super-kind of star and hash). Is there a problem with this? Is this a bug?
Or is this simply because type synonyms are implemented before OpenKinds?
More information about the ghc-devs
mailing list