[Haskell-cafe] Monadic style with Streams (as in
Data.Array.Parallel.Stream)
Mark Wassell
mwassell at bigpond.net.au
Sat May 15 21:54:13 EDT 2010
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
More information about the Haskell-Cafe
mailing list