
I'm trying to build a list where each entry depends on the previous one. Unfoldr seemed like a good idea at the time. Unfortunately, my values are monadic values (specifically RVars, from the random-fu package). Okay, shouldn't be a problem; I just monadic bind and...
-- example code updateCell :: Bool -> RVar Bool updateCell False = return False updateCell True = bernoulli (0.9 :: Double)
sim = sequence $ take 20 $ unfoldr (\x -> Just (x, x >>= updateCell)) (return True)
runRVar sim DevURandom [True,True,True,True,True,False,True,False,True,False,False,False,False,False,False,True,True,False,False,False]
That output shouldn't be possible if I'm doing things right... It appears that each cell has an independent history. I'm stumped. Advice on threading monad input in general and random-fu in specific would be appreciated. -- Alex R

On Monday 13 September 2010 20:42:49, Alex Rozenshteyn wrote:
I'm trying to build a list where each entry depends on the previous one. Unfoldr seemed like a good idea at the time. Unfortunately, my values are monadic values (specifically RVars, from the random-fu package). Okay, shouldn't be a problem; I just monadic bind and...
-- example code updateCell :: Bool -> RVar Bool updateCell False = return False updateCell True = bernoulli (0.9 :: Double)
sim = sequence $ take 20 $ unfoldr (\x -> Just (x, x >>= updateCell))
(return True)
So you get sequence [return True , return True >>= updateCell , (return True >>= updateCell) >>= updateCell , ((return True >>= updateCell) >>= updateCell) >>= updateCell , ... ]
runRVar sim DevURandom
[True,True,True,True,True,False,True,False,True,False,False,False,False, False,False,True,True,False,False,False]
That output shouldn't be possible if I'm doing things right... It appears that each cell has an independent history. I'm stumped. Advice on threading monad input in general and random-fu in specific would be appreciated.
What you want would be something like iterateM :: (Monad m) => (a -> m a) -> a -> m [a] iterateM act start = do next <- act start rest <- iterateM act next return (start : rest) but that would only work if the bind is sufficiently lazy, otherwise you'd have to iterate a given number of times.

Is there a way to take a given monad's bind and wrap it to make it more
lazy? It doesn't seem like there should be, but I'm being hopeful.
On Mon, Sep 13, 2010 at 3:21 PM, Daniel Fischer
On Monday 13 September 2010 20:42:49, Alex Rozenshteyn wrote:
I'm trying to build a list where each entry depends on the previous one. Unfoldr seemed like a good idea at the time. Unfortunately, my values are monadic values (specifically RVars, from the random-fu package). Okay, shouldn't be a problem; I just monadic bind and...
-- example code updateCell :: Bool -> RVar Bool updateCell False = return False updateCell True = bernoulli (0.9 :: Double)
sim = sequence $ take 20 $ unfoldr (\x -> Just (x, x >>= updateCell))
(return True)
So you get
sequence [return True , return True >>= updateCell , (return True >>= updateCell) >>= updateCell , ((return True >>= updateCell) >>= updateCell) >>= updateCell , ... ]
runRVar sim DevURandom
[True,True,True,True,True,False,True,False,True,False,False,False,False, False,False,True,True,False,False,False]
That output shouldn't be possible if I'm doing things right... It appears that each cell has an independent history. I'm stumped. Advice on threading monad input in general and random-fu in specific would be appreciated.
What you want would be something like
iterateM :: (Monad m) => (a -> m a) -> a -> m [a] iterateM act start = do next <- act start rest <- iterateM act next return (start : rest)
but that would only work if the bind is sufficiently lazy, otherwise you'd have to iterate a given number of times.
-- Alex R

On Mon, Sep 13, 2010 at 7:53 PM, Alex Rozenshteyn
Is there a way to take a given monad's bind and wrap it to make it more lazy? It doesn't seem like there should be, but I'm being hopeful.
I wouldn't bother with that. Just write the following and be happy =). iterateM :: (Monad m) => Int -> (a -> m a) -> a -> m [a] iterateM 0 _ _ = return [] iterateM n act start = do next <- act start rest <- iterateM (n-1) act next return (start : rest) However, I think the answer of your question is "no". And in cases where you can do something similar (e.g. in IO you can use unsafeInterleaveIO), most of the time it isn't the best solution. Cheers! -- Felipe.

The reason I ask is that I plan on making a simulation, which will run until
the user decides to pause.
Potentially, I could keep state and update it, but that doesn't seem
haskelly. With an infinite list, I even get history for free.
On Mon, Sep 13, 2010 at 7:34 PM, Felipe Lessa
On Mon, Sep 13, 2010 at 7:53 PM, Alex Rozenshteyn
wrote: Is there a way to take a given monad's bind and wrap it to make it more lazy? It doesn't seem like there should be, but I'm being hopeful.
I wouldn't bother with that. Just write the following and be happy =).
iterateM :: (Monad m) => Int -> (a -> m a) -> a -> m [a] iterateM 0 _ _ = return [] iterateM n act start = do next <- act start rest <- iterateM (n-1) act next return (start : rest)
However, I think the answer of your question is "no". And in cases where you can do something similar (e.g. in IO you can use unsafeInterleaveIO), most of the time it isn't the best solution.
Cheers!
-- Felipe.
-- Alex R

Daniel Fischer wrote:
What you want would be something like
iterateM :: (Monad m) => (a -> m a) -> a -> m [a] iterateM act start = do next <- act start rest <- iterateM act next return (start : rest)
but that would only work if the bind is sufficiently lazy, otherwise you'd have to iterate a given number of times.
Daniel's explanation is exactly right - unfoldr doesn't work "in the monad", and you need a function like this iterateM that does. Unfortunately (as he hints) this exact function won't work because it tries to compute an infinite list, which RVar can't do in finite time. Intstead, I would recommend starting with a function such as iterateM and modifying it to accept a "number of steps" parameter - effectively fusing the "take" step into the "unfoldr" step from your original example - or to use some other knowledge of your algorithm to limit the size of the list generated. For example, truncating the output when the cell changes to False. That would be a bit silly in this example since then your output would just be a variable-length list of "True"s, but I imagine this is just a simplification of what you're really trying to accomplish anyway. I'm pretty sure it would not be possible to make the bind lazy (even when the remaining computation uses no entropy), because if nothing else the bind operation would have to search the remaining (infinite) computation to make sure it isn't going to require any more random sampling. Lazily sampling the random variables wouldn't be an option either - that would effectively require a generalized unsafeInterleaveIO which is somehow able to work in any monad, since RVars can be run in all kinds of monads - State, IO, "ContT (FooT BarM)", etc. - anything that has a 'RandomSource' or 'MonadRandom' instance. Incidentally, the type of "unfoldr (\x -> Just (x, x >>= updateCell))" gives a valuable clue about the behavior you can expect from it. Its type is [RVar Bool], which is a list of random variables. Every RVar is (by design) independent from all others, so that type just can't describe the operation you want. "iterateM updateCell True" has the type you need, which is "RVar [Bool]". -- James

related question: is this also an example of para morphism?
here is my current understanding
cata morphism -> fold/reduce [ e.g. list of numbers -> sum of numbers]
ana morphism -> unfold/reproduce depending on input [ e.g. one number ->
list of reapeated instances of same number]
some functions like map can be written both as a cata and as an ana.
hylo morphism -> ana followed by cata [ e.g. recursion trees of function
calls are ana, and the return path to the final evaluation is cata]
para morphism -> kind of ana but depends on input and output generated so
far fib, fact etc?
Im not sure i understood the last one well.
Thanks
Cheers
Ram
On Mon, Sep 13, 2010 at 11:42 AM, Alex Rozenshteyn
I'm trying to build a list where each entry depends on the previous one. Unfoldr seemed like a good idea at the time. Unfortunately, my values are monadic values (specifically RVars, from the random-fu package). Okay, shouldn't be a problem; I just monadic bind and...
-- example code updateCell :: Bool -> RVar Bool updateCell False = return False updateCell True = bernoulli (0.9 :: Double)
sim = sequence $ take 20 $ unfoldr (\x -> Just (x, x >>= updateCell)) (return True)
runRVar sim DevURandom
[True,True,True,True,True,False,True,False,True,False,False,False,False,False,False,True,True,False,False,False]
That output shouldn't be possible if I'm doing things right... It appears that each cell has an independent history. I'm stumped. Advice on threading monad input in general and random-fu in specific would be appreciated.
-- Alex R
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On 13 September 2010 20:24, Sriram Durbha
para morphism -> kind of ana but depends on input and output generated so far fib, fact etc? Im not sure i understood the last one well.
No - a paramorphism is a generalization of fold rather than unfold. Basically it is a foldr where you can look further into the input (foldr only lets you see the current element). It is sometimes confusing to use the lookahead as foldr is working "backwards" from the right. An apomorphism is one generalisation of unfold. Apomorphisms are unfolds + a flush operation that operates on the final state. Jeremy Gibbons has a number of papers that are useful here - most other presentations build *-morphisms with fixed point functors. See the 'fission' paper for paramorphism and the paper 'Metamorphisms: Streaming representation-changers' for apomorphism. http://www.comlab.ox.ac.uk/jeremy.gibbons/publications/ The "Arithmetic Coding" papers are also worth reading for this topic.
participants (6)
-
Alex Rozenshteyn
-
Cook, James A CTR USA USMA
-
Daniel Fischer
-
Felipe Lessa
-
Sriram Durbha
-
Stephen Tetley