{-# 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