{-# OPTIONS -fglasgow-exts #-} module M where import Data.Word import Data.Bits import GHC.Prim import GHC.Word import Test.QuickCheck fhb_boxed :: Word -> Word fhb_boxed w = b1 .|. b2 where b2 = if 0xFFFF0000 .&. w /= 0 then 0x2 else 0 b1 = if 0xFF00FF00 .&. w /= 0 then 0x1 else 0 fhb_ideal :: Word -> Word fhb_ideal (W# w) = W# ((int2Word# (case word2Int# (int2Word# 0xFF00FF00# `and#` w) of 0# -> 0#; _ -> 1#)) `or#` (int2Word# (case word2Int# (int2Word# 0xFFFF0000# `and#` w) of 0# -> 0#; _ -> 2#))) ------------------------------------------------------------------------ -- -- QuickCheck test -- prop_eq n = fhb_boxed w == fhb_ideal w where w = fromIntegral (n :: Int) main = test prop_eq $ ./A OK, passed 100 tests. -}