[Haskell-cafe] Re: Joels Time Leak

Joel Reymont joelr1 at gmail.com
Wed Jan 4 12:15:59 EST 2006


This is my latest version. Based on Don's tweaks.

{-# INLINE sequ #-}

sequ :: (b -> a) -> PU a -> (a -> PU b) -> PU b
sequ a b c | a `seq` b `seq` c `seq` False = undefined
sequ f pa k = PU fn1 fn2 fn3
     where
       {-# INLINE fn1 #-}
       fn1 ptr b =
           case f b of
             a -> case k a of
                    pb -> do ptr' <- appP pa ptr a
                             appP pb ptr' b
       {-# INLINE fn2 #-}
       fn2 ptr = do (a, ptr') <- appU pa ptr
                    case k a of pb -> appU pb ptr'
       {-# INLINE fn3 #-}
       fn3 b = case f b of
                 a -> case k a of
                        pb -> do sz1 <- appS pa a
                                 sz2 <- appS pb b
                                 return $! sz1 + sz2

On Jan 4, 2006, at 4:18 PM, Bulat Ziganshin wrote:

> are you tried to inline it? and all other pickling combinators
>
> the problem is what when you write
>
> put (Cmd a b) = do putWord16 a; putWord32 b
>
> and inline putWord16/putWord32, you can be sure that you will get
> sequencing for free. but what is a pickling combinators? it's a
> high-order functions, which combines drivers for simple types like
> Word16 to final driver which can read entire Command. the principial
> question - will this final driver be interpreted, i.e. executed as a
> large number of enclosed calls to pickler combination functions, or it
> will be compiled, i.e. executed as simple sequence of getByte calls,
> which then builds the final value. in first case your program will
> spend all its time in these combinator funtions calls, so you will not
> have much effect from using Ptrs in elementary picklers

--
http://wagerlabs.com/







More information about the Haskell-Cafe mailing list