runtime fusion for Data.ByteString.cons ?
Donald Bruce Stewart
dons at cse.unsw.edu.au
Sun Nov 19 18:44:41 EST 2006
dons:
> claus.reinke:
> > I noticed that ByteString is drastically slower than String if I use
> > cons a lot. according to the source, that is expected because of
> > the memcpy for the second parameter.
>
> Just a quick response, before I consider this in detail, in the stream
> fusion branch of Data.ByteString cons is fusible:
>
> cons :: Word8 -> ByteString -> ByteString
> cons c (PS x s l) = unsafeCreate (l+1) $ \p -> withForeignPtr x $ \f -> do
> poke p c
> memcpy (p `plusPtr` 1) (f `plusPtr` s) (fromIntegral l)
> {-# INLINE [1] cons #-}
>
> {-# RULES
> "FPS cons -> fused" [~1] forall w.
> cons w = F.strTransformerUp (F.consS w)
> "FPS cons -> unfused" [1] forall w.
> F.strTransformerUp (F.consS w) = cons w
> #-}
>
> strTransformerUp :: (Stream -> Stream) -> (ByteString -> ByteString)
> strTransformerUp f = writeStrUp . f . readStrUp
> {-# INLINE [0] strTransformerUp #-}
>
> consS :: Word8 -> Stream -> Stream
> consS w (Stream nextx xs0 len) = Stream next' (True :*: xs0) (len+1)
> where next' (True :*: xs) = Yield w (False :*: xs)
> next' (_ :*: xs) = case nextx xs of
> Done -> Done
> Skip xs' -> Skip (False :*: xs')
> Yield x xs' -> Yield x (False :*: xs')
> {-# INLINE [0] consS #-}
Oh, this is slower than it should be, too. Those Bools get in the way of
GHC's specConstr optimisation. Instead it shoudl use a strict Either.
consS :: Word8 -> Stream -> Stream
consS w (Stream nextx xs0 len) = Stream next' (RightS xs0) (len+1)
where next' (RightS xs) = Yield w (LeftS xs)
next' (LeftS xs) = case nextx xs of
Done -> Done
Skip xs' -> Skip (LeftS xs')
Yield x xs' -> Yield x (LeftS xs')
{-# INLINE [0] consS #-}
where
data EitherS a b = LeftS !a | RightS !b deriving (Eq, Ord )
that should help a bit with the stripping away of constructors in consS.
-- Don
More information about the Glasgow-haskell-users
mailing list