> 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 for the Port library.  (a portable core-functionality library).
I think that it nicely shows the difference between a library with a nice convenience
layer, like GIO, and a bare gui library like Port. It also shows that Port is still at a
reasonably high-level from a gui perspective: writing this example with just the Win32
library for example is much more work.

All the best,
    Daan.

{--------------------------------------------------------------------------------
This program implements the "goodbye" demo as posted by John Meacham on
the Haskell GUI mailing list.
--------------------------------------------------------------------------------}
module Main where
import Graphics.UI.Port
main = do demo    -- setup gui
          start   -- start event loop
 
demo :: IO ()
demo
  = do w <- createWindow
       registerWindow w                               -- register for proper shutdown when the window is closed
       registerWindowDismiss w (closeWindow w)        -- close when the user dismisses the window
       registerWindowPaint w (\can upd -> fillRect upd can) -- fill the background with some color
       setWindowDomainSize w (Size 0 0)               -- no scroll bars needed
       setWindowViewSize w (Size 80 40)               -- guess some size as Port has no layout manager
       setWindowTitle w "Bye!"                        -- set the title bar text
      
       l <- createLabel w
       setLabelText l "Hello World!"
       lsize <- getLabelRequestSize l                 -- get the minimal size of the label
       moveResizeControl l (rectAt (Point 0 0) lsize) -- position in upperleft corner
       b <- createButton w
       setButtonText b "Bye"
       bsize <- getButtonRequestSize b                -- get the minimal size of the button
       moveResizeControl b (rectAt (Point 0 (sh lsize)) bsize)  -- position under the label
       registerButtonClick b (bye w l b)              -- register event handler
       showWindow w                                   -- show it all
  where
    -- called on the first click with the window, label, and button as arguments.
    bye w l b
      = do setLabelText l "Goodbye"
           registerButtonClick b (closeWindow w)      -- overwrite the old event handler