[Haskell-cafe] Optimization help needed
Joel Reymont
joelr1 at gmail.com
Thu Dec 22 11:27:17 EST 2005
Folks,
These functions together can be taking 15-20% of my processing time.
I'm trying to optimize the hell out of them. Would it be less
expensive to convert each of them into a foreign function?
Is there a way to optimize them further within Haskell? appU_wstr is
particularly expensive and deals with reversing the words in a
unicode string received little-endian.
Thanks, Joel
P.S
appP_wstr :: Ptr Word8 -> Int -> String -> IO Int
appP_wstr ptr ix [] = pickle short ptr ix 0
appP_wstr ptr ix a =
do ix1 <- foldM (\ix' c -> pickle endianW16 ptr ix' $ word c) ix a
pickle short ptr ix1 0
where word c = fromIntegral $ ord c
appU_wstr :: Ptr Word8 -> Int -> IO (String, Int)
appU_wstr ptr ix =
do (a, ix1) <- unpickle endianW16 ptr ix
appU_wstr' ix1 a []
where appU_wstr' ix 0 acc =
return $!! (reverse acc, ix)
appU_wstr' ix x acc =
do (a, ix1) <- unpickle endianW16 ptr ix
appU_wstr' ix1 a ((chr $ fromIntegral x):acc)
{-# SPECIALIZE swap16 :: Word16 -> Word16 #-}
{-# SPECIALIZE swap16 :: Int16 -> Int16 #-}
swap16 :: Bits a => a -> a
#ifdef BIG_ENDIAN
swap16 v = (v `shiftR` 8) .|. (v `shiftL` 8)
#else
swap16 v = v
#endif
{-# SPECIALIZE swap32 :: Word32 -> Word32 #-}
{-# SPECIALIZE swap32 :: Int32 -> Int32 #-}
swap32 :: Bits a => a -> a
#ifdef BIG_ENDIAN
swap32 v = ( v `shiftR` 24) .|.
((v .&. 0x000000FF) `shiftL` 24) .|.
((v .&. 0x0000FF00) `shiftL` 8) .|.
((v .&. 0x00FF0000) `shiftR` 8)
#else
swap32 v = v
#endif
{-# SPECIALIZE swap64 :: Word64 -> Word64 #-}
{-# SPECIALIZE swap64 :: Int64 -> Int64 #-}
swap64 :: Bits a => a -> a
#ifdef BIG_ENDIAN
swap64 v = ( v `shiftR` 56) .|.
((v .&. 0x00000000000000FF) `shiftL` 56) .|.
((v .&. 0x00FF000000000000) `shiftR` 40) .|.
((v .&. 0x000000000000FF00) `shiftL` 40) .|.
((v .&. 0x0000FF0000000000) `shiftR` 24) .|.
((v .&. 0x0000000000FF0000) `shiftL` 24) .|.
((v .&. 0x000000FF00000000) `shiftR` 8) .|.
((v .&. 0x00000000FF000000) `shiftL` 8)
#else
swap64 v = v
#endif
--
http://wagerlabs.com/
More information about the Haskell-Cafe
mailing list