[Haskell-cafe] GUI programming

Mario Blažević mblazevic at stilo.com
Fri Feb 5 13:54:23 EST 2010


Victor Nazarov wrote:
> Hello,
> 
> I've been writing some GUI application with Gtk2hs. It's an
> interpreter for lambda-calculus and combinatory logic, it's GPL and if
> you interested I can share it with cafe.
> 
> The problem is that the GUI code has become very ugly and I'm tempted
> to rewrite it totally. I've been looking forward to the FRP stuff, but
> I've never seen a single definition of the term. Conal Eliot's
> "denotational programming" is too general to be definition. I want to
> try Grapefruit, but I got totally lost when I see arrow notation.
> 
> I consider more lightweight and more imperative approach, something
> closer to CSP (Communicating Secuential Processes) then FRP. I've just
> crafted some sample program to illustrate my idea.
> 
> The behaviour is a monad and it's IO monad so you can do any IO
> (Gtk2hs) programming you wish. The differences is that you don't
> attach static event handlers and tries to determine what to do
> dependent on application state. You attach and detach handlers as much
> as possible. Behaviour looks like a process that can stop execution
> and wait for some GUI event. When event arrived it continues
> execution.

	To summarize, the behaviour is a suspendable IO computation. It looks 
very much like a coroutine, in fact. I'm planning to extract the 
Control.Concurrent.Coroutine module [1] into a separate package soon. It 
implements a similar concept but generalized to transform any monad and 
any functorial suspension.

[1] 
http://hackage.haskell.org/packages/archive/scc/0.4/doc/html/Control-Concurrent-Coroutine.html


> Do you see this approach viable. There are steel some details to emerge:
> * How to wait for several events
> * How to handle IO exceptions

	I don't really know how applicable the idea is to GUI programming. 
That's not my area of expertise. I am surprised, though, that neither 
your code not your comments seem to address the issue of concurrency, as 
I expect that would be crucial in a GUI setting. Wouldn't you need 
different behaviours to run in different threads?

> 
> Here is the code:
> {-# LANGUAGE ExistentialQuantification #-}
> ...


	I don't see the purpose of your BBind constructor. It seems to me that 
you could simply move the first three cases of runBehaviour 
implementation into your >>= and get rid of the constructor. Do you 
need that much laziness?


> import Data.IORef
> import System.Glib
> import Graphics.UI.Gtk
> import Control.Monad.Trans
> 
> type Event obj = IO () -> IO (ConnectId obj)
> 
> data Behaviour a =
>   forall b. BBind (Behaviour b) (b -> Behaviour a)
>   | BIO (IO a)
>   | forall obj. GObjectClass obj => BWaitEvent (Event obj) (Behaviour a)
> 
> instance Monad Behaviour
>  where action >>= generator = BBind action generator
>        return a = BIO (return a)
> 
> instance MonadIO Behaviour
>  where liftIO action = BIO action
> 
> runBehaviour :: Behaviour a -> IO a
> runBehaviour (BBind (BWaitEvent event after) f) = runBehaviour
> (BWaitEvent event (after >>= f))
> runBehaviour (BBind (BIO a) f) = a >>= \x -> runBehaviour (f x)
> runBehaviour (BBind (BBind a f) g) = runBehaviour (a >>= (\x -> f x >>= g))
> runBehaviour (BIO a) = a
> runBehaviour (BWaitEvent event after) =
>  do sigIdRef <- newIORef (error "You can't access sigIdRef before
> signal is connected")
>     sigId <- event $
>       do sigId <- readIORef sigIdRef
>          signalDisconnect sigId
>          runBehaviour after
>          return ()
>     writeIORef sigIdRef sigId
>     return (error "You can't expect result from behaviour")
> 
> waitEvent :: GObjectClass obj => Event obj -> Behaviour ()
> waitEvent event = BWaitEvent event (return ())
> 
> main :: IO ()
> main =
>   do initGUI
>      window <- windowNew
>      onDestroy window mainQuit
>      set window [windowTitle := "Hello World"]
>      button <- buttonNew
>      let buttonB label =
>            do liftIO $ set button [buttonLabel := label]
>               waitEvent (onClicked button)
>               buttonB (label ++ "*")
>      runBehaviour (buttonB "*")
>      set window [containerChild := button]
>      widgetShowAll window
>      mainGUI
> 
> 
> 
> 
> ------------------------------------------------------------------------
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


-- 
Mario Blazevic
mblazevic at stilo.com
Stilo International

This message, including any attachments, is for the sole use of the
intended recipient(s) and may contain confidential and privileged
information. Any unauthorized review, use, disclosure, copying, or
distribution is strictly prohibited. If you are not the intended
recipient(s) please contact the sender by reply email and destroy
all copies of the original message and any attachments.


More information about the Haskell-Cafe mailing list