[Haskell-cafe] My try for a CoroutineT monad tranformer

2008-04-25 Thread Joachim Breitner
Hi,

(for those who follow planet.haskell.org this is old news, but I thought
I’d tell the others)

In
http://www.joachim-breitner.de/blog/archives/291-Pausable-IO-actions-for-better-GUI-responsiveness.html
I describe how I wrote a monad transformer that allows me to pause a
computation from within by returning another computation that I can use
to re-start the computation (or to throw it away if I want). I needed
this for a long running drawing computation in a gtk2hs program that I
want to pause at convenient points (to allow user interaction), and that
I need to abort when what I’m drawing is not up-to-date anymore.

The API basically consists of the function
 runCoroutineT :: Monad m = CoroutineT m () - m (Maybe (CoroutineT m ()))
which runs the pausable computation, any Maybe returns Just the resume
action, and the function
 pause :: Monad m = CoroutineT m ()
to be used inside the computation, which pauses it.

I have put the complete module in the darcs repository that might later
also contain the GUI program at http://darcs.nomeata.de/FrakView/

What do you think of CoroutineT? Could it have been easily implemented
using the existing monad transformers? Is it useful enough so that it
should be included somewhere, and where? Are there any problems with
strictness or other tripping points that I have overlooked?

Greetings,
Joachim
-- 
Joachim Breitner
  e-Mail: [EMAIL PROTECTED]
  Homepage: http://www.joachim-breitner.de
  ICQ#: 74513189
  Jabber-ID: [EMAIL PROTECTED]


signature.asc
Description: Dies ist ein digital signierter Nachrichtenteil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] My try for a CoroutineT monad tranformer

2008-04-25 Thread Dan Weston
I guess like minds think alike! See the very recent e-mail thread 
started by Ryan Ingram:

http://thread.gmane.org/gmane.comp.lang.haskell.cafe/39155/focus=39159

Take a look at the code referenced in Luke Palmer's reply:
http://luqui.org/git/?p=luqui-misc.git;a=blob;f=work/code/haskell/frp/Fregl/Suspend.hs

A snippet follows:

 class (Monad m) = MonadSuspend v m | m - v where
   attempt :: m a - m (Either a (v - m a))
   suspend :: m v

 newtype SuspendT v m a
   = SuspendT { runSuspendT :: m (Either a (v - SuspendT v m a)) }

Your (Coroutine m a) appears to be isomorphic to (SuspendT () m a) [so 
Coroutine m () = SuspendT () m ()]


Your runCoroutineT appears to be isomorphic to a specialization of 
runSuspendT:


runSuspendT' :: SuspendT () m () - m (Either () (() - SuspendT () m ()))

Here the () - a ~ a and Either () a ~ Maybe a

Dan

Joachim Breitner wrote:

Hi,

(for those who follow planet.haskell.org this is old news, but I thought
I’d tell the others)

In
http://www.joachim-breitner.de/blog/archives/291-Pausable-IO-actions-for-better-GUI-responsiveness.html
I describe how I wrote a monad transformer that allows me to pause a
computation from within by returning another computation that I can use
to re-start the computation (or to throw it away if I want). I needed
this for a long running drawing computation in a gtk2hs program that I
want to pause at convenient points (to allow user interaction), and that
I need to abort when what I’m drawing is not up-to-date anymore.

The API basically consists of the function

runCoroutineT :: Monad m = CoroutineT m () - m (Maybe (CoroutineT m ()))

which runs the pausable computation, any Maybe returns Just the resume
action, and the function

pause :: Monad m = CoroutineT m ()

to be used inside the computation, which pauses it.

I have put the complete module in the darcs repository that might later
also contain the GUI program at http://darcs.nomeata.de/FrakView/

What do you think of CoroutineT? Could it have been easily implemented
using the existing monad transformers? Is it useful enough so that it
should be included somewhere, and where? Are there any problems with
strictness or other tripping points that I have overlooked?

Greetings,
Joachim




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


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


Re: [Haskell-cafe] My try for a CoroutineT monad tranformer

2008-04-25 Thread Joachim Breitner
Hi,

Am Freitag, den 25.04.2008, 11:49 -0700 schrieb Dan Weston:
 I guess like minds think alike! See the very recent e-mail thread 
 started by Ryan Ingram:
 http://thread.gmane.org/gmane.comp.lang.haskell.cafe/39155/focus=39159
 
 Take a look at the code referenced in Luke Palmer's reply:
 http://luqui.org/git/?p=luqui-misc.git;a=blob;f=work/code/haskell/frp/Fregl/Suspend.hs
 
 A snippet follows:
 
   class (Monad m) = MonadSuspend v m | m - v where
 attempt :: m a - m (Either a (v - m a))
 suspend :: m v
  
   newtype SuspendT v m a
 = SuspendT { runSuspendT :: m (Either a (v - SuspendT v m a)) }
 
 Your (Coroutine m a) appears to be isomorphic to (SuspendT () m a) [so 
 Coroutine m () = SuspendT () m ()]
 
 Your runCoroutineT appears to be isomorphic to a specialization of 
 runSuspendT:
 
 runSuspendT' :: SuspendT () m () - m (Either () (() - SuspendT () m ()))
 
 Here the () - a ~ a and Either () a ~ Maybe a

You are quite right, it really is the same thing. The implementation
behind runCoroutineT is not just a specialization, but the exact same
thing (with Left and Right switched). I just put the specialization
there because I had no need for a return value in my use case.

And interesting how Ryan and me had the same thoughts on the same day.
Maybe the April 24th should be considered Suspend You Monadic Action
Day.

Greetings,
Joachim

-- 
Joachim Breitner
  e-Mail: [EMAIL PROTECTED]
  Homepage: http://www.joachim-breitner.de
  ICQ#: 74513189
  Jabber-ID: [EMAIL PROTECTED]


signature.asc
Description: Dies ist ein digital signierter Nachrichtenteil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] My try for a CoroutineT monad tranformer

2008-04-25 Thread Dan Weston
Is there a Haskell Wiki page (or blog) on Monad Suspension? This looks 
like a nice paradigm that apfelmus points out can be used to 
considerably shorten your code, but only if the rest of us learn how!


If not, maybe someone can be persuaded to write one?

Dan

Joachim Breitner wrote:

Hi,

Am Freitag, den 25.04.2008, 11:49 -0700 schrieb Dan Weston:
I guess like minds think alike! See the very recent e-mail thread 
started by Ryan Ingram:

http://thread.gmane.org/gmane.comp.lang.haskell.cafe/39155/focus=39159

Take a look at the code referenced in Luke Palmer's reply:
http://luqui.org/git/?p=luqui-misc.git;a=blob;f=work/code/haskell/frp/Fregl/Suspend.hs

A snippet follows:

  class (Monad m) = MonadSuspend v m | m - v where
attempt :: m a - m (Either a (v - m a))
suspend :: m v
 
  newtype SuspendT v m a
= SuspendT { runSuspendT :: m (Either a (v - SuspendT v m a)) }

Your (Coroutine m a) appears to be isomorphic to (SuspendT () m a) [so 
Coroutine m () = SuspendT () m ()]


Your runCoroutineT appears to be isomorphic to a specialization of 
runSuspendT:


runSuspendT' :: SuspendT () m () - m (Either () (() - SuspendT () m ()))

Here the () - a ~ a and Either () a ~ Maybe a


You are quite right, it really is the same thing. The implementation
behind runCoroutineT is not just a specialization, but the exact same
thing (with Left and Right switched). I just put the specialization
there because I had no need for a return value in my use case.

And interesting how Ryan and me had the same thoughts on the same day.
Maybe the April 24th should be considered Suspend You Monadic Action
Day.

Greetings,
Joachim





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


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


Re: [Haskell-cafe] My try for a CoroutineT monad tranformer

2008-04-25 Thread David Menendez
On Fri, Apr 25, 2008 at 3:45 PM, Dan Weston [EMAIL PROTECTED] wrote:
 Is there a Haskell Wiki page (or blog) on Monad Suspension? This looks like
 a nice paradigm that apfelmus points out can be used to considerably
 shorten your code, but only if the rest of us learn how!

There are a few papers which deal with resumption monads, which appear
to be closely related.

You can also express CoroutineT (or something very much like it) using
a free monad.

data Term f a = Var a | Branch (f (Term f a))

instance Functor f = Monad (Term f) where
return = Var

Var a = f = f a
Branch as = f = Branch (fmap (= f) as)


lift :: (Functor f) = f a - Term f a
lift m = Branch (fmap Var m)

runTerm :: (Monad m) = Term m () - m (Maybe (Term m ()))
runTerm (Var ())   = return Nothing
runTerm (Branch m) = fmap Just m

pause :: (Monad m) = Term m ()
pause = Branch (return (Var ()))

Note that runTerm and pause really only require Applicative.

I believe Suspend can be implemented similarly. Note that SuspendT v
m a is isomorphic to m (Term (ReaderT v m) a).

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe