On Friday 13 March 2009, Cristiano Paris wrote:
> 2009/3/13 Marcin Kosiba <marcin.kos...@gmail.com>:
> > Hi,
> >        I've already checked those out. I tried using your yield
> > implementation and while it works, I couldn't get it to work with the
> > state monad.
> >        So while:
> > data RecPair a b = Nil | RP (b, a -> RecPair a b)
> > yield x = Cont $ \k -> RP (x, k)
> >
> >        got me half-way to my goal, I couldn't figure out how to make
> > something like:
> >
> > yield' = do
> >  state <- get
> >  state' <- yield state
> >  put state'
>
> Basically, the yield is built upon the Cont monad which has a
> transformer counter part, ContT. You could try and re-implement the
> yield under ContT instead of just Cont then you can stack ContT on top
> of State (or StateT if you need more monads) and have a state (i.e.
> get/put) and the yield.

Great! That helped a lot. I'm attaching a ConT yield implementation and 
another one which also handles a return statement with a different type. Hope 
someone finds them useful.
        
Thanks!
        Marcin Kosiba
{-# OPTIONS -XNoMonomorphismRestriction #-}
module Main where

import Control.Monad
import Control.Monad.Cont
import Control.Monad.State
import Control.Monad.Identity

data (Monad m) => RecPair m a b = Nil | RP (b, a -> m (RecPair m a b))

yield :: (Monad m) => r -> ContT (RecPair m a r) m a
yield x = ContT $ \k -> return $ RP(x, k)

f'cps = return 2

test = do
  x <- f'cps
  yield x
  yield (x + 1)
  return ()

testSt :: (MonadState s m, Num s) => ContT (RecPair m a s) m ()
testSt = do
  y <- f'cps
  v <- get
  put (y + 1)
  yield v
  v' <- get
  yield v'
  return ()

getRP :: RecPair Identity a a -> [a]
getRP Nil = []
getRP (RP (b, f)) = b : (getRP $ runIdentity $ f b)

runYield :: ContT (RecPair m a1 b) Identity a -> RecPair m a1 b
runYield f = runIdentity $ runContT f (\_ -> return Nil)

--result is [2,3]
runTest = getRP $ runYield test

getRPSt :: (RecPair (State t) a a, t) -> [a]
getRPSt (Nil, _) = []
getRPSt (RP (b, f), s) = b : (getRPSt $ runState (f b) s)

runYieldSt :: (Num s) => s -> (RecPair (State s) a s, s)
runYieldSt iState = runState (runContT testSt (\_ -> return Nil)) iState

--result is [iState, 3]
runTestSt iState = getRPSt $ runYieldSt iState
{-# OPTIONS -XNoMonomorphismRestriction #-}
module Main where

import Control.Monad
import Control.Monad.Cont
import Control.Monad.State
import Control.Monad.Identity

data (Monad m) => RecPair m a b r = Nil r | RP (b, a -> m (RecPair m a b r))

yield :: (Monad m) => r -> ContT (RecPair m a r v) m a
yield x = ContT $ \k -> return $ RP(x, k)

f'cps = return 2

test = do
  x <- f'cps
  yield x
  yield (x + 1)
  return (-1)

testSt = do
  y <- f'cps
  v <- get
  put (y + v)
  yield v
  testSt

getRP :: RecPair Identity a a a -> [a]
getRP (Nil x) = [x]
getRP (RP (b, f)) = b : (getRP $ runIdentity $ f b)

runYield :: ContT (RecPair m a1 b a) Identity a -> RecPair m a1 b a
runYield f = runIdentity $ runContT f (\x -> return $ Nil x)

--result is [2,3, -1]
runTest = getRP $ runYield test

getRPSt :: (RecPair (State t) v v v, t) -> [v]
getRPSt (Nil x, _) = [x]
getRPSt (RP (b, f), s) = b : (getRPSt $ runState (f b) s)

runYieldSt :: ContT (RecPair m a1 b a) (State s) a
              -> s
              -> (RecPair m a1 b a, s)
runYieldSt f iState = runState (runContT f (\x -> return $ Nil x)) iState

--result is [iState, iState + 2..]
runTestSt iState = getRPSt $ runYieldSt testSt iState

Attachment: signature.asc
Description: This is a digitally signed message part.

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to