(state) monad and CPS

Hello, I would like to get some advice about state monad (or any other monad I guess) and CPS. Let's take a simple exemple (see the code below) 'walk' is a function written in CPS that compute the number of nodes & leaves in a tree. It use a counter which is explicitly passed through calls. 'walk2' is does the same using the state monad but is not written in CPS Is it possible to write a function 'walk3' written in CPS and using the state monad? Thank you Regards J-C module M where import Control.Monad.State data Node = Node (Node, Int, Node) |Leaf Int |Empty deriving (Show) walk Empty acc k = k acc walk (Leaf _) acc k = k (acc+1) walk (Node (l, _, r)) acc k = let k1 acc = walk r acc k in walk l (acc+1) k1 nb = Node (Leaf 1, 2, Leaf 3) nd = Node (nb, 4, Empty) nh = Node (Empty, 8, Leaf 9) ng = Node (Leaf 6, 7, nh) ne = Node (nd, 5, ng) r = walk ne 0 id walk2 Empty = return () walk2 (Leaf _ ) = do acc <- get put (acc+1) return () walk2 (Node (l, _, r)) = do acc <- get put (acc+1) walk2 l walk2 r return () r2 = runState (walk2 ne) 0

Yes; check out the module "Control.Monad.Cont", which has a monad for continuation passing style. In particular, note that most of the monads in Control.Monad.* are "stackable" in that there is a version of the monad which you can stack on top of an existing monad. So for example, you could use ContT to stack the CPS monad on top of the State monad, or StateT to stack the State monad on top of the CPS monad. Hope this helps, Greg On Nov 10, 2009, at 12:18 PM, jean-christophe mincke wrote:
Hello,
I would like to get some advice about state monad (or any other monad I guess) and CPS.
Let's take a simple exemple (see the code below)
'walk' is a function written in CPS that compute the number of nodes & leaves in a tree. It use a counter which is explicitly passed through calls. 'walk2' is does the same using the state monad but is not written in CPS
Is it possible to write a function 'walk3' written in CPS and using the state monad?
Thank you
Regards
J-C
module M where
import Control.Monad.State
data Node = Node (Node, Int, Node) |Leaf Int |Empty deriving (Show)
walk Empty acc k = k acc walk (Leaf _) acc k = k (acc+1) walk (Node (l, _, r)) acc k = let k1 acc = walk r acc k in walk l (acc+1) k1
nb = Node (Leaf 1, 2, Leaf 3) nd = Node (nb, 4, Empty)
nh = Node (Empty, 8, Leaf 9) ng = Node (Leaf 6, 7, nh)
ne = Node (nd, 5, ng)
r = walk ne 0 id
walk2 Empty = return () walk2 (Leaf _ ) = do acc <- get put (acc+1) return () walk2 (Node (l, _, r)) = do acc <- get put (acc+1) walk2 l walk2 r return ()
r2 = runState (walk2 ne) 0
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Something like this should work:
newtype ContState r s a = ContState { runCS :: s -> (a -> s -> r) -> r }
instance Monad (ContState r s) where
return a = ContState $ \s k -> k a s
m >>= f = ContState $ \s0 k -> runCS m s $ \a s1 -> runCS (f a) s1 k
instance MonadState s (ContState r s) where
get = ContState $ \s k -> k s s
put s = ContState $ \_ k -> k () s
instance MonadCont (ContState r s) where
callCC f = ContState $ \s0 ka -> runCS (f $ \a -> ContState $ \s1
kb -> ka a s1) s0 ka
There's a design choice as to whether the inner continuation should be
called with s0 or s1; it depends if you want the continuation from
callCC to abort any state changes or preserve them up to that point.
-- ryan
On Tue, Nov 10, 2009 at 12:18 PM, jean-christophe mincke
Hello,
I would like to get some advice about state monad (or any other monad I guess) and CPS.
Let's take a simple exemple (see the code below)
'walk' is a function written in CPS that compute the number of nodes & leaves in a tree. It use a counter which is explicitly passed through calls. 'walk2' is does the same using the state monad but is not written in CPS
Is it possible to write a function 'walk3' written in CPS and using the state monad?
Thank you
Regards
J-C
module M where
import Control.Monad.State
data Node = Node (Node, Int, Node) |Leaf Int |Empty deriving (Show)
walk Empty acc k = k acc walk (Leaf _) acc k = k (acc+1) walk (Node (l, _, r)) acc k = let k1 acc = walk r acc k in walk l (acc+1) k1
nb = Node (Leaf 1, 2, Leaf 3) nd = Node (nb, 4, Empty)
nh = Node (Empty, 8, Leaf 9) ng = Node (Leaf 6, 7, nh)
ne = Node (nd, 5, ng)
r = walk ne 0 id
walk2 Empty = return () walk2 (Leaf _ ) = do acc <- get put (acc+1) return () walk2 (Node (l, _, r)) = do acc <- get put (acc+1) walk2 l walk2 r return ()
r2 = runState (walk2 ne) 0
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Excerpts from jean-christophe mincke's message of Tue Nov 10 21:18:34 +0100 2009:
Hello, Hello,
I would like to get some advice about state monad (or any other monad I guess) and CPS.
Here is to remarks somewhat off topic: [...]
walk Empty acc k = k acc walk (Leaf _) acc k = k (acc+1) walk (Node (l, _, r)) acc k = let k1 acc = walk r acc k in walk l (acc+1) k1
Remember that by default laziness and accumulators does not fits well together. Here you are probably building a chain of thunks. Making acc a strict argument (using !acc) or using 'seq' (acc `seq` ...) will cure this. [...]
do acc <- get put (acc+1) ...
Since this pattern occurs often 'modify' is a combination of get and put: do modify (+1) ... About your CPS question, you should have a look at the 'transformers' package, in particular the Control.Monad.Trans.Cont [1] module. [1]: http://hackage.haskell.org/packages/archive/transformers/0.1.4.0/doc/html/Co... Best regards, -- Nicolas Pouillard http://nicolaspouillard.fr

Nicolas Pouillard wrote:
Excerpts from jean-christophe mincke's message of Tue Nov 10 21:18:34 +0100 2009:
do acc <- get put (acc+1) ...
Since this pattern occurs often 'modify' is a combination of get and put:
do modify (+1) ...
Though the caveat about laziness applies here as well. modify is famously lazy which can lead to space leaks and stack overflows. Better would be to define and use your own strict version: modify' f = get >>= \x -> put $! f x -- Live well, ~wren

Hello,
Thank everybody for the answers.
I must admit that I did not really emphasize the goal behind my initial
question. Which is better expressed this way:
'walk' is written is CPS and is tail recursive. Unless I am wrong , if the
continuation monad is used, the recursive calls to 'walk' are no longer in
tail position.
So my initial question was rather: is it possible to use the state monad and
keeping the code tail recursive?
I do not master all the subtilities of lazy evaluation yet and perhaps tail
recursivity does not have the same importance (or does not offer the same
guarantees) in a lazy language as it does in a strict language.
But I am facing a similar problem with workflows in F# (F#'s monads).
Thank you
Regards
J-C
On Thu, Nov 12, 2009 at 8:17 AM, wren ng thornton
Nicolas Pouillard wrote:
Excerpts from jean-christophe mincke's message of Tue Nov 10 21:18:34 +0100 2009:
do acc <- get put (acc+1) ...
Since this pattern occurs often 'modify' is a combination of get and put:
do modify (+1) ...
Though the caveat about laziness applies here as well. modify is famously lazy which can lead to space leaks and stack overflows. Better would be to define and use your own strict version:
modify' f = get >>= \x -> put $! f x
-- Live well, ~wren
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

jean-christophe mincke wrote:
I do not master all the subtilities of lazy evaluation yet and perhaps tail recursivity does not have the same importance (or does not offer the same guarantees) in a lazy language as it does in a strict language.
Yep, that's the case. With lazy evaluation, tail recursion is less important. Also, code that looks tail recursive in a strict language will actually not be tail recursive in Haskell. A well-known example is the definition foldl and applied in the fashion of foldl (+) 0 [0..10] Regards, apfelmus -- http://apfelmus.nfshost.com

Excerpts from wren ng thornton's message of Thu Nov 12 08:17:41 +0100 2009:
Nicolas Pouillard wrote:
Excerpts from jean-christophe mincke's message of Tue Nov 10 21:18:34 +0100 2009:
do acc <- get put (acc+1) ...
Since this pattern occurs often 'modify' is a combination of get and put:
do modify (+1) ...
Though the caveat about laziness applies here as well. modify is famously lazy which can lead to space leaks and stack overflows. Better would be to define and use your own strict version:
modify' f = get >>= \x -> put $! f x
However if you want a strict state you should better use Control.Monad.State.Strict [1]. Finally I'm wondering if [1] is strict enough... [1]: http://www.haskell.org/ghc/docs/latest/html/libraries/mtl/Control-Monad-Stat... -- Nicolas Pouillard http://nicolaspouillard.fr
participants (6)
-
Gregory Crosswhite
-
Heinrich Apfelmus
-
jean-christophe mincke
-
Nicolas Pouillard
-
Ryan Ingram
-
wren ng thornton