
Dear List, a little puzzle. Given a monad M with a MonadFix instance, and these two functions: act1 :: T -> M () act2 :: a -> M T I morally want to write this function: foo :: [a] -> M () foo = mdo mapM_ act1 xs xs <- mapM act2 return () Unfortunately, that will not work: mapM_ will force xs before any of it can be generated. But morally it should be possible, as the lists passed to mapM_ and mapM have the same, already known list. So here is my solution (which is a bit more general, because I happen to need some that in one place): mapFstMapSnd :: MonadFix m => [(a -> m (), m a)] -> m () mapFstMapSnd xs = const () `liftM` go xs (return []) where go [] cont = cont go ((f,s):xs) cont = mdo f v (v:vs) <- go xs $ do vs <- cont v <- s return (v:vs) return vs Using that, I can write foo = mapFstSnd . map (x -> (act1, act2 x)) Are there better solutions? Simpler ones? Or possibly ones that do not require a partial pattern? Hmm, and thinking while writing lets me come up with data FunSplit m where FunSplit :: forall m a . (a -> m ()) -> m a -> FunSplit m mapFstMapSnd :: forall m. MonadFix m => [FunSplit m] -> m () mapFstMapSnd xs = const () `liftM` go xs (return ()) where go :: [FunSplit m] -> m b -> m b go [] cont = cont go (FunSplit f s:xs) cont = mdo f v (v,vs) <- go xs $ do vs <- cont v <- s return (v,vs) return vs foo :: [SPut] -> SPut foo = mapFstMapSnd . map go where go x = FunSplit act1 (act2 x) Any suggestions for improvement? Thanks, Joachim -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de Jabber-ID: nomeata@joachim-breitner.de

Hello Joachim,
I don't really understand what you're doing here. There's the obvious
mapM_ (act2 >=> act1)
But presumably act1 performs some monadic action that doesn't depend on its
input, and you need that to be performed before act2?
To me, it feels like there's some sort of implicit coupling between act1
and act2, and you would be better off extracting that, perhaps by changing
act1 to have the type act1 :: M T -> () .
If that's not possible, your approach seems pretty simple to me.
John L.
On Jan 15, 2014 1:57 AM, "Joachim Breitner"
Dear List,
a little puzzle.
Given a monad M with a MonadFix instance, and these two functions: act1 :: T -> M () act2 :: a -> M T
I morally want to write this function: foo :: [a] -> M () foo = mdo mapM_ act1 xs xs <- mapM act2 return ()
Unfortunately, that will not work: mapM_ will force xs before any of it can be generated. But morally it should be possible, as the lists passed to mapM_ and mapM have the same, already known list.
So here is my solution (which is a bit more general, because I happen to need some that in one place):
mapFstMapSnd :: MonadFix m => [(a -> m (), m a)] -> m () mapFstMapSnd xs = const () `liftM` go xs (return []) where go [] cont = cont go ((f,s):xs) cont = mdo f v (v:vs) <- go xs $ do vs <- cont v <- s return (v:vs) return vs
Using that, I can write foo = mapFstSnd . map (x -> (act1, act2 x))
Are there better solutions? Simpler ones? Or possibly ones that do not require a partial pattern?
Hmm, and thinking while writing lets me come up with
data FunSplit m where FunSplit :: forall m a . (a -> m ()) -> m a -> FunSplit m
mapFstMapSnd :: forall m. MonadFix m => [FunSplit m] -> m () mapFstMapSnd xs = const () `liftM` go xs (return ()) where go :: [FunSplit m] -> m b -> m b go [] cont = cont go (FunSplit f s:xs) cont = mdo f v (v,vs) <- go xs $ do vs <- cont v <- s return (v,vs) return vs
foo :: [SPut] -> SPut foo = mapFstMapSnd . map go where go x = FunSplit act1 (act2 x)
Any suggestions for improvement?
Thanks, Joachim
-- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de Jabber-ID: nomeata@joachim-breitner.de
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Dear John, the background is a binary format assembler, so you can think of the monad as the Put monad, only sufficiently lazy to admit a useful MonadFix instance. Then one can do nice things like mdo putWord32 offset putBS someMoreHeaderData ... offset <- getCurrentOffset putBS byteString1 where I conceptually use the offset before it is known. So what if I want to put two offsets, followed by two bytestrings? Easy: mdo putWord32 offset1 putWord32 offset2 putBS someMoreHeaderData ... offset1 <- getCurrentOffset putBS byteString1 offset2 <- getCurrentOffset putBS byteString2 Now I try to generalize that to a list of Bytestrings, and just from the looks of it, this is what you want to do: mdo mapM_ putWord32 offsets putBS someMoreHeaderData ... offsets <- forM byteStrings $ \b -> offset <- getCurrentOffset putBS b return offset but that will <<loop>>. Am Mittwoch, den 15.01.2014, 13:10 -0800 schrieb John Lato:
Hello Joachim, I don't really understand what you're doing here. There's the obvious
mapM_ (act2 >=> act1)
But presumably act1 performs some monadic action that doesn't depend on its input, and you need that to be performed before act2?
Exactly, (act2 >=> act1) would write out the data in the wrong order.
To me, it feels like there's some sort of implicit coupling between act1 and act2, and you would be better off extracting that, perhaps by changing act1 to have the type act1 :: M T -> () .
If that's not possible, your approach seems pretty simple to me.
I don’t think its, possible with that signature, no... (It were if I were to interleave the calls to act1 and act2, instead of requiring first all act1 and then all act2, but then it would be trivial anyways.) Greetings, Joachi -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de Jabber-ID: nomeata@joachim-breitner.de

Joachim Breitner wrote:
the background is a binary format assembler, so you can think of the monad as the Put monad, only sufficiently lazy to admit a useful MonadFix instance. Then one can do nice things like
mdo putWord32 offset putBS someMoreHeaderData ... offset <- getCurrentOffset putBS byteString1
where I conceptually use the offset before it is known.
[..] Now I try to generalize that to a list of Bytestrings, and just from the looks of it, this is what you want to do:
mdo mapM_ putWord32 offsets putBS someMoreHeaderData ... offsets <- forM byteStrings $ \b -> offset <- getCurrentOffset putBS b return offset
but that will <<loop>>.
So, the overall idea is that we can reserve 32 bits for the offset and defer its calculation to later. In other words, putWord32 can "forward the file pointer" long before it actually writes the word. Now, what's the problem with the `offsets` list? I think it may actually work in some monads that have a good MonadFix instance, but often, the MonadFix instances tend to be poor. One noteable example of the latter is the IO monad, and I have found the following rule to be very useful: To use value recursion in the IO monad, make sure that the sequence of *computations* is always defined in advance, only the values that these computations operate on may be lazy. This rule is best explained with the problem at hand, by asking the following question: how many `putWord32` instructions does the following expression generate? mapM_ putWord32 offsets Clearly, it should be `length offsets` many, but the problem is that this number is not known until the spine of `offsets` has been calculated. Now, some monads may be able to do that, but the rule for IO is that the number of `putWord32` must be known before the later definition of `offsets` can yield a value different from _|_ at all. Now, if a recursive expression works in the IO monad, then it will work in any other monad as well. Fortunately, we do known the spine of `offsets` in advance: it has the same spine as `byteStrings`. The solution is to make that explicit in the code, by using a lazy `zip`: ... mapM_ putWord32 (offsets `spine` byteStrings) ... where spine :: [a] -> [void] -> [a] spine ~[] [] = [] spine ~(x:xs) (y:ys) = x : tag xs ys This code takes the spine of `byteStrings` and fills it with values from `offsets`. It may also be possible to get rid of the <<loop>> by defining the monad appropriately: one pass calculates all offsets, a second pass calculates the actual output. The spine of `offsets` does not depend on the offset calculation, so there is a good chance that this might work recursively. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Hi, Am Donnerstag, den 16.01.2014, 11:34 +0100 schrieb Heinrich Apfelmus:
Fortunately, we do known the spine of `offsets` in advance: it has the same spine as `byteStrings`. The solution is to make that explicit in the code, by using a lazy `zip`:
... mapM_ putWord32 (offsets `spine` byteStrings) ...
where spine :: [a] -> [void] -> [a] spine ~[] [] = [] spine ~(x:xs) (y:ys) = x : tag xs ys
This code takes the spine of `byteStrings` and fills it with values from `offsets`.
I thought about something in that direction; but thanks for working it out. What I do not like about this solution is that it is not safe: As a programmer I have two make sure that offsets and byteStrings actually have the same length. Greetings, Joachim -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de Jabber-ID: nomeata@joachim-breitner.de
participants (3)
-
Heinrich Apfelmus
-
Joachim Breitner
-
John Lato