> 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.
Hi all, here is the goodbye demo in ObjectIO.
It shows nicely how a gui in the ObjectIO library is decribed
purely as a datatype (i.e. Dialog in this case) and how it maintains
local state for you.
 
All the best,
    Daan.
 
ps. Off course, I am not an ObjectIO expert so maybe Peter van Achten
has an even nicer solution.
 
pps. Everyone with a recent ghc on windows can run this program at home:  ghci ByeDemo.hs -package objectio

{--------------------------------------------------------------------------------
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.
This demo also uses a nice layout: the label and button are centered
in the dialog. Instead of a window, a dialog is used since it resizes
automatically to accomodate the controls.
The dialog maintains a boolean local state that says whether the button
is clicked for the first time or not. (The process state is unused.)
When the button is clicked the "bye" function is called. This function
checks the local state to see whether this is the first time that it is called.
If so it changes the text of the label and updates the local state.
Otherwise it closes the process.
--------------------------------------------------------------------------------}
module Main where
import Graphics.UI.ObjectIO
main
  = do displayId <- openId
       startIO NDI () (openDialog True (dialog displayId)) []  -- local state = True, process state = ()
  where  
    dialog displayId
      = Dialog "Bye!"
        (   TextControl "Hello World"
            [ControlPos (Center,zero), ControlId displayId]
        :+: ButtonControl "Bye"
            [ControlPos (Center,zero), ControlFunction bye]
        )
        [WindowClose (noLS closeProcess)]
      where
        -- called on a button click with a local state/process state tuple.
        bye (firstTime,ps)
          | firstTime  = do setControlText displayId "Goodbye"
                            return (False,ps)
          | otherwise  = do closeProcess ps
                            return (False,ps)