Monadic style with Streams (as in Data.Array.Parallel.Stream)

Hi, This possibly might go against the spirit of what Stream programming is about but I having difficulties converting an imperative algorithm [1] into Haskell and think it would be easier if I was able to write it in a monadic style with operations to read and write from and to the streams. I first tried to approach it by delving into the innards of other Stream functions to devise what I needed. I only got so far and the sticking point was defining the Monad. I then approached it from the Monad side and although what I have is workable, it probably isn't going to perform (for one it uses fromStream and tailS on each read off the front of the stream). So: 1. Is this monadic style within the spirit of what Stream programming is about? 2. Is there anyway to do this more elegantly and without the user of fromStream and tailS, for example. This is the workable solution I have: module StreamMonad where import Data.Array.Parallel.Stream import Data.Monoid import Control.Monad.Writer import Control.Monad.State instance Monoid (Stream a) where mempty = emptyS mappend = (+++) type SM a b c = StateT (Stream a) (Writer (Stream b)) c readS :: SM a b a readS = do s <- get let a = head $ fromStream s put $ tailS s return a writeS :: b -> SM a b () writeS x = tell $ singletonS x t1' :: SM (Int,Int) Int () t1' = mapM_ (\_ -> do (x,y) <- readS writeS x writeS y) [1..2] t1 = fromStream $ snd $ runWriter $ runStateT t1' $ toStream [(1,2),(3,4)] -- At least this works .. t2 = fromStream $ snd $ runWriter $ runStateT t1' $ toStream [(2*x-1,2*x) | x <- [1..] ] Cheers Mark [1] The arithmentic coding and decoding algorithms given in http://mattmahoney.net/dc/dce.html#Section_32

Hi Mark What style of "Stream programming" do you have in mind? In Haskell there can be at least four styles of Stream programming depending how you count: There is the stream as infinite-list - see Wouter Swierstra's Data.Stream on Hackage and if you have university affiliation look for the paper "Functional Pearl: Streams and Unique Fixed Points" by Ralf Hinze. I think comonadic stream programming is within this style - if not that makes five styles... There's "Stream fusion" (Duncan Coutts, Roman Leshchinskiy, Don Stewart) where the stream programming is an implementation technique for particular data-structures - internally recursion is avoided with a special unfold to get fusion optimizations. Then there is the Arrow Stream processor style of writing transducers, used I think by the Fudgets toolkit - streamproc on Hackage. Possibly not finally, there is Jeremy Gibbons's 'Streaming representation-changers' style which has relation to the Stream fusion style but appears to have different aims - see "Arithmetic coding with folds and unfolds" with Richard Bird. None of them are monadic I'm afraid. The "Arithmetic coding..." paper might be relevant if you are working with Huffman coding. http://www.cse.unsw.edu.au/~dons/papers/stream-fusion.pdf http://www.comlab.ox.ac.uk/jeremy.gibbons/publications/ Best wishes Stephen

On 16/05/2010, at 11:54, Mark Wassell wrote:
Hi,
This possibly might go against the spirit of what Stream programming is about but I having difficulties converting an imperative algorithm [1] into Haskell and think it would be easier if I was able to write it in a monadic style with operations to read and write from and to the streams.
I first tried to approach it by delving into the innards of other Stream functions to devise what I needed. I only got so far and the sticking point was defining the Monad. I then approached it from the Monad side and although what I have is workable, it probably isn't going to perform (for one it uses fromStream and tailS on each read off the front of the stream).
Data.Array.Parallel.Stream serves only one purpose: to represent loops produced by DPH in such a way that the compiler is able to optimise them well. Putting a monad on top of that will very very likely break this. To be honest, I'm not sure why you need the monad anyway. I would expect compression/decompression to be pure functions of type Stream Word8 -> Stream Word8. In any case, I would urgently recommend not to use Data.Array.Parallel.Stream for anything at this point. This whole subsystem will soon die of old age and be replaced by the much nicer stuff from package vector, specifically Data.Vector.Fusion.Stream and Data.Vector.Fusion.Stream.Monadic. Note that the latter implements monadic streams as described in http://www.cse.unsw.edu.au/~rl/publications/recycling.html. Perhaps those can be useful for you if you really need a monad. Roman

Roman Leshchinskiy wrote:
On 16/05/2010, at 11:54, Mark Wassell wrote:
Hi,
This possibly might go against the spirit of what Stream programming is about but I having difficulties converting an imperative algorithm [1] into Haskell and think it would be easier if I was able to write it in a monadic style with operations to read and write from and to the streams.
I first tried to approach it by delving into the innards of other Stream functions to devise what I needed. I only got so far and the sticking point was defining the Monad. I then approached it from the Monad side and although what I have is workable, it probably isn't going to perform (for one it uses fromStream and tailS on each read off the front of the stream).
Data.Array.Parallel.Stream serves only one purpose: to represent loops produced by DPH in such a way that the compiler is able to optimise them well. Putting a monad on top of that will very very likely break this. To be honest, I'm not sure why you need the monad anyway. I would expect compression/decompression to be pure functions of type Stream Word8 -> Stream Word8.
In any case, I would urgently recommend not to use Data.Array.Parallel.Stream for anything at this point. This whole subsystem will soon die of old age and be replaced by the much nicer stuff from package vector, specifically Data.Vector.Fusion.Stream and Data.Vector.Fusion.Stream.Monadic. Note that the latter implements monadic streams as described in http://www.cse.unsw.edu.au/~rl/publications/recycling.html. Perhaps those can be useful for you if you really need a monad.
Roman
Thanks. No, I don't need a Monad and I suspected it was a bad idea. It was really needed for convenience as all I had to go on was a C implementaiton of arithmetic coding (which included a getc part-way through the code block which I hoped to map to something like a get from the stream). However thanks to Stephen I have something better to work from. I will also take a look at Data.Vector.Fusion.Stream. Cheers Mark
participants (3)
-
Mark Wassell
-
Roman Leshchinskiy
-
Stephen Tetley