
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. Do you see this approach viable. There are steel some details to emerge: * How to wait for several events * How to handle IO exceptions Here is the code: {-# LANGUAGE ExistentialQuantification #-} module Main where 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 -- Victor Nazarov

Hello Victor,
2010/2/2, Victor Nazarov
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.
Sure, why not?
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.
All this process calculus stuff reminds me of Fudgets. Maybe this approach is more pragmatic at the moment: even more so, I think it's theoretical underpinnings are appealing as well. Who said that all programming should be reduced to pure functions? :-) As a side note, there's a book "How to Design Worlds" which discusses interactive purely functional programming (using games as an example). While it is only tangentially related to GUI programming, I wonder if their approach can be adapted for use in GUIs. Cheers, Artyom Shalkhakov
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.
Do you see this approach viable. There are steel some details to emerge: * How to wait for several events * How to handle IO exceptions
Here is the code: {-# LANGUAGE ExistentialQuantification #-} module Main where
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
-- Victor Nazarov

Victor Nazarov wrote:
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))
Just a minor note: you can somewhat clean up your code by using a generic monad, as implemented in my cabal package operational http://hackage.haskell.org/package/operational and described in Heinrich Apfelmus. The Operational Monad Tutorial. In http://themonadreader.wordpress.com/2010/01/26/issue-15/ Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Wed, Feb 3, 2010 at 4:11 PM, Heinrich Apfelmus
Victor Nazarov wrote:
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))
Just a minor note: you can somewhat clean up your code by using a generic monad, as implemented in my cabal package operational
http://hackage.haskell.org/package/operational
and described in
Heinrich Apfelmus. The Operational Monad Tutorial. In http://themonadreader.wordpress.com/2010/01/26/issue-15/
Thank you. It seems relevant. I'll have a look at it. Speaking about packages. What is current community status of monad transformers packages. I'm using MonadIO class and there are mtl, monads-fd, monads-tf packages that provide it. I personally prefer type families to functional dependencies. Should I use monads-tf, or should I stick to mtl? -- Victor Nazarov

Victor Nazarov wrote:
Speaking about packages. What is current community status of monad transformers packages. I'm using MonadIO class and there are mtl, monads-fd, monads-tf packages that provide it. I personally prefer type families to functional dependencies. Should I use monads-tf, or should I stick to mtl?
As I understand it, mtl is to be replaced by transformers and one of the monads-* packages in the future, though there is no clear recommendation yet. See also http://thread.gmane.org/gmane.comp.lang.haskell.libraries/12229/ Also, it seems that there is currently no community preference choice for either type families or functional dependencies. Personally, I didn't want to think about this and simply chose mtl . But if you like type families a lot, I see no problem with going ahead and using transformers + monads-tf . Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

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.
This is not what you are looking for, but if you also want to check something extremely less powerfull but extremely more simple, you may consider this sugestion I made some time ago for a GUI library: http://article.gmane.org/gmane.comp.lang.haskell.cafe/66638 Best, Maurício

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-Concurr...
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Mario Blazevic mblazevic@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.

On Fri, Feb 5, 2010 at 9:54 PM, Mario Blažević
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-Concurr...
Yes, behaviour is exactly a coroutine. Your coroutine module seem cool, but I would like to have a DSL closer to GUI programming than to concurrent programming.
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?
As I understand Gtk2hs still don't run in -threaded environment. And I've been trying to avoid multithreading as much as possible. I've already implemented exception handling through MonadError instance and multi-event waits. Now I'm trying to rewrite GUI code of my lambda-interpreter, and I'll publish it on hackage, when I am done.
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?
I think, I need it, I can't see the way to rewrite it without intermediate data-structure. The problem is the third case: runBehaviour (BBind (BBind a f) g) = runBehaviour (a >>= (\x -> f x >>= g)) See Heinrich Apfelmus' entry in Monad.Reader to see operational view on monads. My implementation is very close to this idea. -- Victor Nazarov

Hello Felipe, Monday, February 8, 2010, 1:10:07 PM, you wrote:
As I understand Gtk2hs still don't run in -threaded environment.
It does run, just use unsafeInitGUIForThreadedRTS.
... and run all GUI primitives via special wrapper or in GUI thread -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (7)
-
Artyom Shalkhakov
-
Bulat Ziganshin
-
Felipe Lessa
-
Heinrich Apfelmus
-
Mario Blažević
-
Maurício CA
-
Victor Nazarov