Terminology (Re: [GUI] Re: Know you backends)
Antony Courtney
antony@apocalypse.org
Fri, 31 Jan 2003 16:08:04 -0500
This is a multi-part message in MIME format.
--------------040600050701030508060204
Content-Type: text/plain; charset=us-ascii; format=flowed
Content-Transfer-Encoding: 7bit
John Meacham 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.
Although (as I have said repeatedly) Fruit is far too experimental to be
suitable as a standardized, portable production GUI toolkit, I have,
just for fun, implemented this little excercise in Fruit. Code is attached.
-antony
--
Antony Courtney
Grad. Student, Dept. of Computer Science, Yale University
antony@apocalypse.org http://www.apocalypse.org/pub/u/antony
--------------040600050701030508060204
Content-Type: text/plain;
name="HelloGoodbye.as"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline;
filename="HelloGoodbye.as"
--
-- HelloGoodbye -- simple "Hello/Goodbye" example for GUI API comparison
-- proposed by John Meacham
--
-- Author: Antony Courtney, 1/31/03
module HelloGoodbye where
import GUI
import Arrow
import AFRP
import Haven
import GAUtils
-- The code here is short, but heavily commented. I've chosen to err
-- on the side of verbosity with comments to try and describe a little
-- of the design methodology and clarify many of the combinators that are
-- relatively newer than published papers on Fruit or AFRP/Yampa.
-- First, let's try to seperate the "model" from the interface:
-- Our application model is a signal function that accepts button
-- press events as input, and produces a String to display paired with
-- an event that occurs when the application is done executing:
appModel :: SF (Event ()) (String, Event ())
-- Our model is a simple state machine. We'll use kSwitch to switch
-- from the "hello" state to the "goodbye" state on a button press:
appModel = kSwitch helloSF -- initial signal function
(arr fst) -- switch when input event occurs
(\_ _ -> goodbyeSF) -- SF to switch in to
-- The "hello" state just outputs "hello" and does not cause
-- a program termination event:
helloSF :: SF (Event ()) (String,Event ())
helloSF = (constant ("Hello World", noEvent))
-- The "goodbye" state outputs "Goodbye", and produces a program termination
-- event when the input event occurs:
goodbyeSF :: SF (Event ()) (String,Event ())
goodbyeSF = (constant "Goodbye") &&& identity
-- Now for the GUI itself:
-- The window content (or view) consists of a button and label. The
-- String to display in the label is taken as an external signal (from
-- the model), and the button press events are an output signal (to be
-- fed to the model)
-- Some notes:
-- - "GA" is the type of a GUI Arrow, which uses the order in which GUIs
-- appear in the Arrow notation to determine the order in which the
-- GUI components will be layed out.
-- - We use "hbox" to create a horizontal layout of GUI components.
-- - The use of "id" as the input signal to the button specifies default
-- configuration options for the button.
-- - Since there is no returnA at the end of the proc, the output signal
-- from the button is the output signal of the entire GUI
viewGA :: GA (String) (Event ())
viewGA = hbox $ proc s -> do
ltext s >- label -> _
id >- button (btext "Bye")
-- Use feedback to wire the view to the model. The one subtlety here
-- is that we must use 'iPre' to introduce an infinitesimal delay between
-- the output signal of the view and the input signal of the model to ensure
-- that the feedback loop is well-formed.
appGUI :: GUI () (Event ())
appGUI = proc (gin,_) -> do
rec (gin,s) >- unGA viewGA -> (pic,clickE)
clickE >- iPre noEvent -> dClickE
dClickE >- appModel -> (s,termE)
(pic,termE) >- returnA
-- Full Disclosure: The above code assumes that 'runGUI' observes the
-- output event of the GUI, and exits the program when the event occurs.
-- The current implementation doesn't actually support this, but adding
-- it would be trivial.
--
-- Main :: IO ()
-- main = runGUI appGUI
--------------040600050701030508060204--