[Haskell-beginners] How to call popCnt64#?
Michael Snoyman
michael at snoyman.com
Sun Mar 20 14:12:42 UTC 2016
Here's an example:
{-# LANGUAGE MagicHash #-}
import GHC.Prim
import GHC.Types
import Data.Word
main :: IO ()
main = do
let word = 5 :: Word
res =
case word of
W# w -> W# (popCnt64# w)
print res
On Sun, Mar 20, 2016 at 12:19 PM, John Ky <newhoggy at gmail.com> wrote:
> Hello Haskellers,
>
> Does anyone know how to call popCnt64# from the GHC.Prim module?
>
> This was my failed attempt:
>
> λ> popCnt64# 1
>
>
> <interactive>:14:11:
> Couldn't match kind ‘*’ with ‘#’
> When matching types
> a0 :: *
> Word# :: #
> Expected type: Integer -> Word#
> Actual type: Integer -> a0
> In the first argument of ‘popCnt64#’, namely ‘1’
> In the expression: popCnt64# 1
> In an equation for ‘it’: it = popCnt64# 1
>
> -John
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/beginners/attachments/20160320/8eb9396c/attachment.html>
More information about the Beginners
mailing list