Hi All,
 
> --- Krasimir Angelov wrote:
>
> Maybe the wxWindows backed will be good starting
> point for the first working prototype. I still prefer
> native WIN32 and GTK backends but this is just my own
> preference.
 
To help this discussion, I have put the haddock generated
interface of the core wxHaskell binding on the web, so everyone
can see how it looks like.
 
http://wxhaskell.sourceforge.net/doc/wxh
 
Some html files are about 3mb in size, so it can take a while
to download.
 
(and yes, it is on sourceforge but I wouldn't recommend anyone
to try to build it yet as everything is still very initial).
 
All the best,
    Daan.
 
----------- and the bye-demo again ----------------
{--------------------------------------------------------------------------------
This program implements the "goodbye" demo as posted by John Meacham on
the Haskell GUI mailing list. The program is specified as:
I propose a simple program which pops up a window saying 'Hello World' 
with a button saying 'Bye' which you click and it changes the message
to 'Goodbye'. if you click the button again the program exits.
When the button is clicked the first time, it calls "onCommand1". This function 
changes the text of the label and installs another event handler on the button
that closes the main frame. (by default, wxWindows exits the gui when all
windows are closed).
--------------------------------------------------------------------------------}
module ByeDemo where
import Graphics.UI.WXH
main :: IO ()
main 
  = run gui
gui :: IO ()
gui
  = do -- create top frame
       f <- frameCreateTopFrame "Bye demo"
       f # windowSetBackgroundColour white
       -- create text and button control
       t <- staticTextCreate f idDefault "Hello World" rectNull 0
       b <- buttonCreate f idDefault "Bye" rectNull 0
     
       -- put the button underneath the text
       tsize <- t # windowGetSize
       b # windowMove (pt 0 (sh tsize))
       -- resize the frame around the controls
       bsize <- b # windowGetSize
       f # windowSetClientSize (sz (max (sw tsize) (sw bsize)) (sh tsize + sh bsize))
       -- set command handler on the button
       b # buttonOnCommand (onCommand1 f t b)
       -- show the frame
       f # windowShow
       f # windowRaise
       return ()
  where
    -- call on the first click
    onCommand1 f t b
      = do t # controlSetLabel "Goodbye!"
           b # buttonOnCommand (onCommand2 f)
           return ()
    -- call on the second click
    onCommand2 f
      = do f # windowClose False
           return ()