[Haskell-cafe] Arrows and pickler combinators
Jeremy Shaw
jeremy.shaw at linspireinc.com
Thu Dec 22 15:25:40 EST 2005
At Thu, 22 Dec 2005 11:26:51 +0000,
Joel Reymont wrote:
>
> 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.
Last weekend, I hacked up a pickling/unpickling library of my own. The
code is currently a little confusing because I decided to change the
naming scheme half way through. So, don't assume to much from the
names of things.
darcs get http://www.n-heptane.com/nhlab/repos/BerkeleyDB
The file you are interested in is Binary.hs.
-== Short Summary ==-
My library splits the pickling into two parts you can mix and match.
(1) the part that turns a value into a byte stream
(2) the part that reads/writes values from/to the byte stream
-== Core of pickler ==-
My pickling/unpickling code is based around the data type:
data BinParser state m a = BinParser { runBinParser :: state -> m (a, state) }
This type is used for both pickling and unpickling (the type needs a
better name). It is abstracted over three types:
state - for the pickler, state will hold the data that has currently been pickled.
for the unpickler, state will hold the data to unpickle.
m - a monad of your choice
a - the value being pickled/unpickled
The reason for abstracting over state is to allow you to pickle
directly to [Word8], Ptr Word8, or whatever else you wish to
implement. Some times a monad my be needed for reading/writing the
state. For example, Ptr Word8 requires the IO monad. If you don't
really need a monad, then the Identity monad can be used.
-== BinParser Monad Instance ==-
The monad instance for BinParser is pretty straight-forward:
-- A monad instance for BinParser
instance (Monad m) => Monad (BinParser state m) where
return a = BinParser (\s -> return (a, s))
bp >>= f = BinParser ( \state ->
do (a, state') <- runBinParser bp state
runBinParser (f a) state'
)
As I mentioned before, BinParser is used for both pickling *and*
unpickling. Normally we think of Parsers as consuming the state, but
there is no reason the 'parser' can not instead produce the state.
Also, note that this monad instance is not very specific to
pickling/unpickling at all. It is pretty much just a state monad. As a
matter of fact, I hope to be able to switch to Control.Monad.State
when I have time to work on this again.
-== Adding new 'states' to pickle/unpickle ==-
To add a new type of state to pickle/unpickle, you just add a new
instance to this class (once again, needs a better name):
class (Monad m) => BinState s m where
getWord8 :: BinParser s m Word8
putWord8 :: Word8 -> BinParser s m ()
For example:
instance BinState (Ptr Word8) IO where
getWord8 = BinParser $ \p -> do v <- peek p
return (v, advancePtr p 1)
putWord8 w = BinParser $ \p -> do poke p w
return ((), advancePtr p 1)
-== pickle vs. unpickle ==-
Here is where we actually combine the above to do pickling (once
again, naming should be updated):
class ToBin state m a where
binary :: a -> BinParser state m ()
unbinary :: BinParser state m a
Here is a simple pickler for 'Char'
-- May want to store as 4 bytes to support Unicode later.
instance (BinState state m) => ToBin state m Char where
binary c = putWord8 (fromIntegral (ord c))
unbinary =
do w <- getWord8
return $! (chr (fromIntegral w))
Here is a pickler for lists that shows the monad usage a bit better:
instance (BinState state m, ToBin state m a) => ToBin state m [a] where
binary l =
do binary (length l)
mapM_ binary l
unbinary = getList
getList :: (BinState state m, ToBin state m a) => BinParser state m [a]
getList =
do len <- getInt
replicateM len unbinary
-== User Friendly Interface ==-
binary/unbinary are not very user friendly interfaces, so we also
define some user friendly interefaces. If I switched to
Control.Monad.State, I could just use the similar interfaces defined
there...
pickleM/unpickleM is useful if your state requires a monad.
-- NOTE: you may need to force the type to get this to work
-- eg. pickleM "hi" :: IO [Word8]
pickleM :: (Monad m, ToBin state m a) => state -> a -> m state
pickleM initState a =
do (_,finalState) <- (runBinParser (binary a) initState)
return finalState
-- NOTE: you may need to force the type to get this to work
-- eg. fromBin (unPickleM "hi" :: [Word8]) :: IO String
unpickleM :: (Monad m, ToBin state m a) => state -> m a
unpickleM state =
do (a,_) <- runBinParser unbinary state
return a
pickle/unpickle are useful if your state does not need a monad.
-- Some pickler's may not need to run inside a monad, in which case we
-- can use these varients to avoid the monad
pickle :: (ToBin state Identity a) => state -> a -> state
pickle initState value = runIdentity (pickleM initState value)
unpickle :: (ToBin state Identity a) => state -> a
unpickle state = runIdentity (unpickleM state)
-== Example Usage ==-
Here is an example of using the picklers:
-- First define some data types to pickle
data Foo
= Bar String
| Baz Int Char
deriving Show
data FooBar a = FooBar a
deriving Show
-- Use TH to derive some piclkers
$( mkBinInstance ''Foo )
$( mkBinInstance ''FooBar)
-- try them out
-- NOTE: not sure if I am using the terms monomorphic/polymorphic
-- correctly
main = -- first pickle/unpickle a monomorphic (?) type
do print (unpickle (pickle [] (Bar "hello") :: [Word8]) :: Foo)
-- then pickle/unpickle a polymorphic (?) type
print (unpickle (pickle [] (FooBar (Bar "hello")) :: [Word8]) :: (FooBar Foo))
-- use a pickler that outputs to (Ptr Word) instead of [Word8]
allocaBytes 512 $ \ (p :: Ptr Word8) ->
do encoded <- pickleM p (Baz 4 'd')
decoded <- unpickleM p :: IO Foo
print decoded
-== Summary ==-
As I mentioned, the current implementation is a bit of hack-job, but I
think the design is somewhat compelling because of the flexibility
gained by seperating the pickling/unpickling from the mechanism used
to write/read the bytes.
I hope to clean to code up and submit a TMR article eventually.
j.
ps. DStore.hs contains some code for deriving new instances of ToBin (the
pickler/unpickler). I highly recommend you do not look at that code --
I am not sure I even understand how it works anymore :p
More information about the Haskell-Cafe
mailing list