[Haskell-cafe] Arrows and pickler combinators

Joel Reymont joelr1 at gmail.com
Thu Dec 22 06:26:51 EST 2005


Folks,

I'm trying to monadify the pickler code. sequ below positively looks  
like >>= but you can't really join both pickle and unpickle into a  
single monad. I would like to keep the ops together, though, as this  
allows me a single specification for both pickling and unpickling.

Cale suggested that PU is really an arrow in that it supports both  
input and output. I could not find an example of such an arrow,  
though. I thought that it could be a "dual arrow" but then could not  
find a description for one.

I would appreciate your suggestions! The original paper is at http:// 
research.microsoft.com/ ~akenn/fun/picklercombinators.pdf

	Thanks, Joel

P.S.

data PU a = PU
     {
      appP :: Ptr Word8 -> Int -> a -> IO Int,
      appU :: Ptr Word8 -> Int -> IO (a, Int),
      appS :: a -> IO Int
     }

pickle :: PU a -> Ptr Word8 -> Int -> a -> IO Int
pickle p ptr ix value = appP p ptr ix value

unpickle :: PU a -> Ptr Word8 -> Int -> IO (a, Int)
unpickle p ptr ix = appU p ptr ix

sizeup :: PU a -> a -> IO Int
sizeup p value = appS p value

lift :: a -> PU a
lift x = PU (\_ ix _ -> return ix) (\_ ix -> return (x, ix)) (\_ ->  
return 0)

sequ :: (b -> a) -> PU a -> (a -> PU b) -> PU b
sequ f pa k = PU
               (\ptr ix b ->
                    do let a = f b
                           pb = k a
                       ix1 <- appP pa ptr ix a
                       appP pb ptr ix1 b)
               (\ptr ix ->
                    do (a, ix1) <- appU pa ptr ix
                       let pb = k a
                       appU pb ptr ix1)
               (\b ->
                    do let a = f b
                           pb = k a
                       sz1 <- appS pa a
                       sz2 <- appS pb b
                       return $ sz1 + sz2)

pair :: PU a -> PU b -> PU (a,b)
pair pa pb = sequ fst pa (\ a -> sequ snd pb
                           (\ b -> lift $! (a, b)))

--
http://wagerlabs.com/







More information about the Haskell-Cafe mailing list