Actually I think I figured it out:
(>>=) (f c) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs)))
-> (>>=) _(f c)_ (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs)))
-> (>>=) (MN c1) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs)))
-> (\(MN c1) \fc2 -> MN $ \s0 -> let (r1,io1,s1) = c1 s0
( MN c2 ) = fc2 r1
(r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2))
(MN c1) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs)))
-> (MN $ \s0 -> let (r1,io1,s1) = c1 s0
( MN c2 ) = (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) r1
(r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2))
-> (MN $ \s0 -> let (r1,io1,s1) = c1 s0
( MN c2 ) = (>>=) (mapM f cs) (\xs -> return (r1:xs))
(r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2))
-> (MN $ \s0 -> let (r1,io1,s1) = c1 s0
( MN c2 ) = (>>=) (mapM f cs) (\xs -> return (r1:xs))
(r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2))
-> (MN $ \s0 -> let (r1,io1,s1) = c1 s0
( MN c2 ) = (>>=) (mapM f cs) (\xs -> return (r1:xs))
(r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2))
So the "return (r1:xs)" will only happen once the whole mapM has completed,
leaving, if I only use r1 at first, a whole load of partially evaluated
iterations of mapM in the heap.
This also means that sequences such as "mapM x >>= mapM y >>= mapM z" are very
inefficient and should be replaced by mapM (z.y.x) whereever possible.
Agreed?
Sengan
_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell