hrm...
Donald Bruce Stewart
dons at cse.unsw.edu.au
Fri Jan 26 19:41:30 EST 2007
john:
> so I have this simple bit of code, which should be fast but seems to be
> being compiled to something very slow.
>
> > import Data.Word
> > import Data.Bits
> >
> > fhb :: Word -> Word
> > fhb w = b1 .|. b2 where
> > b2 = if 0xFFFF0000 .&. w /= 0 then 0x2 else 0
> > b1 = if 0xFF00FF00 .&. w /= 0 then 0x1 else 0
>
> what it compiles to is something involving Integers, lots of coercions
> and other nasty stuff when it should consist of a couple of primitive
> operations.
looks suspicous!
Ideally I'd want something like this produced:
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#)))
which generates the core:
M.$wfhb_ideal =
\ (ww_sP7 :: GHC.Prim.Word#) ->
GHC.Prim.or#
(GHC.Prim.int2Word#
(case GHC.Prim.word2Int# (GHC.Prim.and# __word 4278255360 ww_sP7) of ds_dMF {
__DEFAULT -> 1; 0 -> 0
}))
(GHC.Prim.int2Word#
(case GHC.Prim.word2Int# (GHC.Prim.and# __word 4294901760 ww_sP7) of ds_dMI {
__DEFAULT -> 2; 0 -> 0
}))
Whereas the test example:
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
Turns into some nasty:
M.lit =
case GHC.Prim.addIntC# 2147418113 2147483647
of wild2_aN5 { (# r_aN7, c_aN8 #) ->
case case c_aN8 of wild3_aN9 {
__DEFAULT ->
case GHC.Prim.int2Integer# 2147418113 of wild4_aNa { (# s_aNc, d_aNd #) ->
case GHC.Prim.int2Integer# 2147483647 of wild5_aNe { (# s1_aNg, d1_aNh #) ->
case GHC.Prim.plusInteger# s_aNc d_aNd s1_aNg d1_aNh
of wild_aO8 { (# s2_aOa, d2_aOb #) ->
GHC.Prim.integer2Word# s2_aOa d2_aOb
}
}
};
0 -> GHC.Prim.int2Word# r_aN7
}
of ww_aNW { __DEFAULT ->
GHC.Word.W# ww_aNW
}
}
M.lit1 :: GHC.Word.Word
[GlobalId]
[Str: DmdType]
M.lit1 =
case GHC.Prim.addIntC# 2130771713 2147483647
of wild2_aN5 { (# r_aN7, c_aN8 #) ->
case case c_aN8 of wild3_aN9 {
__DEFAULT ->
case GHC.Prim.int2Integer# 2130771713 of wild4_aNa { (# s_aNc, d_aNd #) ->
case GHC.Prim.int2Integer# 2147483647 of wild5_aNe { (# s1_aNg, d1_aNh #) ->
case GHC.Prim.plusInteger# s_aNc d_aNd s1_aNg d1_aNh
of wild_aO8 { (# s2_aOa, d2_aOb #) ->
GHC.Prim.integer2Word# s2_aOa d2_aOb
}
}
};
0 -> GHC.Prim.int2Word# r_aN7
}
of ww_aNW { __DEFAULT ->
GHC.Word.W# ww_aNW
}
}
M.$wfhb_boxed :: GHC.Prim.Word# -> GHC.Prim.Word#
[GlobalId]
[Arity 1
Str: DmdType L]
M.$wfhb_boxed =
\ (ww_sPh :: GHC.Prim.Word#) ->
case M.lit1 of wild_aOp { GHC.Word.W# x#_aOr ->
case GHC.Prim.eqWord# (GHC.Prim.and# x#_aOr ww_sPh) __word 0 of wild2_aOk {
GHC.Base.False ->
case M.lit of wild1_XPt { GHC.Word.W# x#1_XPx ->
case GHC.Prim.eqWord# (GHC.Prim.and# x#1_XPx ww_sPh) __word 0 of wild21_XOP {
GHC.Base.False -> __word 3; GHC.Base.True -> __word 1
}
};
GHC.Base.True ->
case M.lit of wild1_XPt { GHC.Word.W# x#1_XPx ->
case GHC.Prim.eqWord# (GHC.Prim.and# x#1_XPx ww_sPh) __word 0 of wild21_XOP {
GHC.Base.False -> __word 2; GHC.Base.True -> __word 0
}
}
}
}
So not sure where those Integer thingies are creeping in.
Here's a little test case, btw, with a QuickCheck property.
-- Don
-------------- next part --------------
{-# 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.
-}
More information about the Glasgow-haskell-users
mailing list