Kind error in GHC-7.4.1, works in GHC-7.2.2
Simon Peyton-Jones
simonpj at microsoft.com
Fri Feb 10 09:40:47 CET 2012
It should not have worked before. Consider
I# $ 3#
($) is a polymorphic function and takes two *pointer* arguments. If we actually called it with I# and 3# as arguments we might seg-fault when we call the GC when allocating the box.
Polymorphic type variables (in this case in the type of ($)) can only be instantiated with boxed types.
Simon
| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-
| users-bounces at haskell.org] On Behalf Of Roel van Dijk
| Sent: 09 February 2012 19:57
| To: glasgow-haskell-users at haskell.org
| Subject: Kind error in GHC-7.4.1, works in GHC-7.2.2
|
| Hello,
|
| I have some code that compiled fine in GHC-7.2.2 but fails in
| GHC-7.4.1 with a kind error.
|
|
| {-# LANGUAGE MagicHash, NoImplicitPrelude, PackageImports #-}
| import "base" Data.Function ( ($) )
| import "base" GHC.Exts ( Int(I#) )
| import "base" Prelude ( Integral, fromIntegral, toInteger )
| import "integer-gmp" GHC.Integer.Logarithms ( integerLogBase# )
|
| intLog :: (Integral a) => a -> a
| intLog x = fromIntegral $ I# $ integerLogBase# 10 (toInteger x)
|
|
| This results in the following error:
|
| Couldn't match kind `#' against `*'
| In the second argument of `($)', namely
| `I# $ integerLogBase# 10 (toInteger x)'
| In the expression:
| fromIntegral $ I# $ integerLogBase# 10 (toInteger x)
| In an equation for `intLog':
| intLog x = fromIntegral $ I# $ integerLogBase# 10 (toInteger x)
|
|
| Simply eliminating some $'s using parenthesis solves the problem:
|
| intLog x = fromIntegral $ I# (integerLogBase# 10 (toInteger x))
|
| Why do I get the above kind error? Could it be a bug in GHC?
|
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list