Kind error in GHC-7.4.1, works in GHC-7.2.2
Roel van Dijk
vandijk.roel at gmail.com
Thu Feb 9 20:56:59 CET 2012
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?
More information about the Glasgow-haskell-users
mailing list