Would be cool to add it to the stdlib. 
Care about a PR? Best add a sample as well. 

Cheers
Dierk

sent from:mobile 

> Am 24.11.2017 um 02:33 schrieb zhou6...@163.com:
> 
> ContT is more pragmatic than Cont,with this powerful abstraction, I could 
> effectively abstract away callbacks and listener in Android. My next 
> exploration is to port coroutineT to Frege
> 
> module examples.MyCont where
> 
> class MonadIO m where
>   --- Lift a computation from the 'IO' monad.
>   liftIO :: IO a -> m a
> 
> class MonadTrans t where
>   --- Lift a computation from the argument monad to the constructed monad.
>   lift :: Monad m => m a -> t m a
> 
> instance MonadIO IO where
>   liftIO io = io
> 
> instance MonadTrans (ContT r) where
>     lift m = ContT (m >>=)
> 
> instance (Monad m, MonadIO m) => MonadIO (ContT r m) where
>     liftIO = lift . liftIO
> 
> data ContT r m a = ContT { runContT :: (a -> m r) -> m r }
> 
> instance Monad (ContT r m) where
>   pure x = contT ($ x)
>   m >>= k = contT $ \c -> runContT m (\x -> runContT (k x) c)
> 
> contT :: ((a -> m r) -> m r) -> ContT r m a
> contT f = ContT { runContT = f }
> 
> runContT :: ContT r m a -> ((a -> m r) -> m r)
> runContT c = ContT.runContT c
> 
> callCC :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a
> callCC f = ContT $ \c -> ContT.runContT (f (\a -> ContT $ \_ -> c a)) c
> 
> data Data = native java.util.Date where
>   native new :: () -> IO (MutableIO Data)
>   native toString :: Mutable s Data -> ST s String
> 
> current :: IO String
> current = do
>   d <- Data.new ()
>   d.toString
> 
> fun :: Int -> IO String
> fun = (`runContT` id) $ do
>   callCC $ \exit1 -> do
>     exit1 $ liftIO current 
> 
> 
> 
> 
> 
> -- 
> You received this message because you are subscribed to the Google Groups 
> "Frege Programming Language" group.
> To unsubscribe from this group and stop receiving emails from it, send an 
> email to frege-programming-language+unsubscr...@googlegroups.com.
> For more options, visit https://groups.google.com/d/optout.

-- 
You received this message because you are subscribed to the Google Groups 
"Frege Programming Language" group.
To unsubscribe from this group and stop receiving emails from it, send an email 
to frege-programming-language+unsubscr...@googlegroups.com.
For more options, visit https://groups.google.com/d/optout.

Reply via email to