[GUI] Re: Terminology
Manuel M T Chakravarty
chak@cse.unsw.edu.au
Thu, 20 Feb 2003 23:48:49 +1100 (EST)
----Next_Part(Thu_Feb_20_23:48:49_2003_353)--
Content-Type: Text/Plain; charset=us-ascii
Content-Transfer-Encoding: 7bit
John Meacham <john@repetae.net> wrote,
> 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 should (hopefully) be a short program with most toolkits and
> demonstrate how one lays out 2 widgets, and responds to user input and
> mutates the display. note, this is not to compare the toolkits
> themselves, but the haskell APIs used to access them.
>
> I'd like to see samples using
>
> gtk+hs
[..]
This request is quite old by now, but I thought I'll provide
you with the Gtk+HS versions of the program nevertheless. I
submit two versions:
* Bye.hs: Based on the plain Gtk+HS API and IORefs (and
naturally very close to the version for gtk2hs).
* IHBye.hs: Based on the iHaskell API, which is a
higher-level API implemented on top of Gtk+HS and part of
the standard Gtk+HS distribution.[1] It's main feature is
to avoid IORef's in favour for a more functional
abstraction called ports.[2] More information is on the
Gtk+HS web page <http://www.cse.unsw.edu.au/~chak/haskell/gtk/>
The attached code requires the current CVS version of Gtk+HS
(to update the button label) and can also be found in the
examples directories in CVS.
Cheers,
Manuel
[1] It is not very complete, though.
[2] It is unfortunate to have a name clash with Daan's Ports
library, but the ports abstraction is being called so
already for many years.
----Next_Part(Thu_Feb_20_23:48:49_2003_353)--
Content-Type: Text/Plain; charset=us-ascii
Content-Transfer-Encoding: 7bit
Content-Disposition: inline; filename="Bye.hs"
-- A little demo program that was proposed on gui@haskell.org to compare
-- toolkit APIs. This is a version for the plain Gtk+HS API.
--
-- There is a single button, which, when clicked once, changes the display
-- and, when clicked a second time, terminates the application.
--
import Monad
import IOExts (IORef, newIORef, readIORef, writeIORef)
import Gtk hiding (init, main)
import qualified
Gtk (init, main)
main :: IO ()
main =
do
Gtk.init Nothing
-- create a new window with a box to pack widgets vertically
--
window <- windowNew WindowToplevel
vbox <- vBoxNew False 10
window `containerAdd` vbox
-- terminate if the window disappears
--
window `signalConnect` WidgetDeleteEventHandler
(\_ _ -> mainQuit >> return False)
-- add the label and button to the box
--
label <- labelNew " Hello World "
button <- buttonNewWithLabel " Bye "
butlbl <- liftM fromWidget $ binGetChild button :: IO Label
boxPackStart vbox label True True 2
boxPackStart vbox button True True 2
-- create a stateful signal handler for the button
--
clickedAlreadyRef <- newIORef False
button `signalConnect` ButtonClickedHandler
(\_ -> do
clickedAlready <- readIORef clickedAlreadyRef
if clickedAlready
then
mainQuit
else do
labelSetText label " Goodbye "
labelSetText butlbl " Exit "
writeIORef clickedAlreadyRef True)
-- display the window and enter the event loop
--
widgetShowAll window
Gtk.main
----Next_Part(Thu_Feb_20_23:48:49_2003_353)--
Content-Type: Text/Plain; charset=us-ascii
Content-Transfer-Encoding: 7bit
Content-Disposition: inline; filename="IHBye.hs"
-- A little demo program that was proposed on gui@haskell.org to compare
-- toolkit APIs. This is a version for the iHaskell API.
--
-- There is a single button, which, when clicked once, changes the display
-- and, when clicked a second time, terminates the application.
--
import Monad
import Gtk (binGetChild)
import IH hiding (init, main)
import qualified
IH (init, main)
main :: IO ()
main =
do
IH.init Nothing
-- create a counter for clicks
--
clicksPort <- newPort 0
-- create the label and button, where the button increments the click count
--
label <- newLabel " Hello World "
button <- newButtonWithLabel " Bye " (clicksPort <-$ (+1))
butlbl <- liftM fromWidget $ binGetChild button :: IO Label
-- pack the label and button vertically and embed them into a window
--
contents <- newBox Vertical True 10 [widget label, widget button]
newWindow " Bye Demo " contents mainQuit False
-- clicks are handled by `handleClick' depending on the number of clicks
--
let
handleClick 2 = mainQuit
handleClick 1 = do
setLabelText label " Goodbye "
setLabelText butlbl " Exit "
clicks <- listenToPort clicksPort
forkIO $ mapM_ handleClick clicks
-- enter the event loop
--
IH.main
----Next_Part(Thu_Feb_20_23:48:49_2003_353)----