[Haskell-cafe] (state) monad and CPS
Gregory Crosswhite
gcross at phys.washington.edu
Tue Nov 10 15:49:20 EST 2009
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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20091110/c53e0ab4/attachment.html
More information about the Haskell-Cafe
mailing list