Difference between revisions of "WxHaskell/Quick start"

From HaskellWiki
Jump to navigation Jump to search
(Deleting page that hasn't been edited for over 10 years)
Line 1: Line 1:
=== A quick start with wxHaskell ===
 
 
This document is written to get you started quickly with writing wxHaskell applications. Further documentation can be found on the [[WxHaskell/Documentation|documentation page]].
 
 
''Note from the author: I have written this page to be in close correspondence with the [http://www.cs.chalmers.se/Cs/Grundutb/Kurser/afp/2005/yahu.html yahu] getting started page – first of all to make my job easier by reusing [http://www.cs.chalmers.se/~koen Koen Claessen's] excellent example, but also since it makes an interesting comparison: we reuse many concepts of yahu, most notably properties and attributes, but as yahu is based on Tcl/TK, the applications are also typed and structured in a fundamentally different way.''
 
 
Daan Leijen
 
 
=== Hello world in wxHaskell ===
 
 
Start your favorite editor and write the following program (that will show a frame with a single button that closes the frame when pressed).
 
 
[[Image:quick1-win.png|Hello world on Windows XP]]
 
<pre>module Main where
 
import Graphics.UI.WX
 
 
main :: IO ()
 
main
 
= start hello
 
 
hello :: IO ()
 
hello
 
= do f&#160;&#160;&#160; &lt;- frame&#160;&#160;&#160; [text := &quot;Hello!&quot;]
 
quit &lt;- button f [text := &quot;Quit&quot;, on command := close f]
 
set f [layout := widget quit]</pre>
 
[[Image:quick1-gtk.png|Hello world on Red Hat Linux]]
 
Now start GHCi and run the program:
 
 
<pre>&gt; ghci -package wx Hello.hs
 
[snip]
 
Loading package wx ... linking ... done.
 
Compiling Main ( Hello.hs, interpreted )
 
Ok, modules loaded: Main.
 
*Main&gt; main</pre>
 
Note: On MacOS X, you can only use the interpreter with special scripts, as you need to build MacOS X ''applications''. Normally, the following commands will do the job:
 
 
ChengWei: On Windows 7, ghci will complain "can't load .so/.DLL for: std c++ ...". But "ghc --make Hello.hs; Hello.exe" on the command line works well.
 
 
[[Image:quick1-mac.png|Hello world sample]]
 
<pre>&gt; ghc -package wx -o hello Hello.hs
 
&gt; /usr/local/wxhaskell/bin/macosx-app -v hello
 
&gt; ./hello</pre>
 
You can read the MacOS X [[WxHaskell/Building_on_MacOS_X|notes]] for more information on using wxHaskell on MacOS X, and how to use it from an interpreter prompt.
 
 
==== Types ====
 
 
A typical wxHaskell program imports the <tt>Graphics.UI.WX</tt> library. If you need to access specific wxWidgets functionality, you would also import the lower level <tt>Graphics.UI.WXCore</tt> library. The <tt>main</tt> function uses <tt>start</tt> to start our GUI. The function <tt>start</tt> initializes the GUI framework with the provided argument and starts the window event loop until the application quits or when all top-level windows are closed. The GUI itself is described with the following functions:
 
 
<pre>frame&#160;&#160;::&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;[Prop&#160;(Frame&#160;())]&#160;-&gt;&#160;IO&#160;(Frame&#160;())
 
button&#160;::&#160;Window&#160;a&#160;-&gt;&#160;[Prop&#160;(Button&#160;())]&#160;-&gt;&#160;IO&#160;(Button&#160;())
 
 
text&#160;&#160;&#160;::&#160;Attr&#160;(Window&#160;a)&#160;String
 
layout&#160;::&#160;Attr&#160;(Frame&#160;a)&#160;&#160;Layout
 
 
(:=)&#160;&#160;&#160;::&#160;Attr&#160;w&#160;a&#160;-&gt;&#160;a&#160;-&gt;&#160;Prop&#160;w
 
set&#160;&#160;&#160;&#160;::&#160;w&#160;-&gt;&#160;[Prop&#160;w]&#160;-&gt;&#160;IO&#160;()
 
 
command::&#160;Event&#160;(Control&#160;a)&#160;(IO&#160;())
 
on&#160;&#160;&#160;&#160;&#160;::&#160;Event&#160;w&#160;a&#160;-&gt;&#160;Attr&#160;w&#160;a
 
 
widget&#160;::&#160;Window&#160;a&#160;-&gt;&#160;Layout</pre>
 
Actually, some of these functions have (even) more general types – you can use the <tt>:t</tt> command in GHCi to see them.
 
 
The types <tt>Frame ()</tt> and <tt>Button ()</tt> denote graphical objects. These objects can have ''properties''. When an object is created we can supply an initial list of properties but we can also set them later using <tt>set</tt>. The type of properties for frames are <tt>Prop (Frame ())</tt> and for buttons <tt>Prop (Button ())</tt>.
 
 
Properties are created by combining ''attributes'' with values. Examples of attributes are <tt>text</tt> and <tt>layout</tt>. An attribute of type <tt>Attr w a</tt> applies to objects of type <tt>w</tt> and values of type <tt>a</tt>. Values can be assigned to attributes using the <tt>(:=)</tt> operator. You can find out more about attributes in the haddock documentation for the modules [http://wxhaskell.sourceforge.net/doc/Graphics-UI-WX-Attributes.html WX.Attributes] and [http://wxhaskell.sourceforge.net/doc/Graphics-UI-WX-Classes.html WX.Classes].
 
 
Somewhat special attributes are ''events''. An event of type <tt>Event w a</tt> can be transformed into an attribute <tt>Attr w a</tt> using <tt>on</tt>. The value of an event attribute is normally an <tt>IO</tt> action that is executed when the event happens. Find out more about events in the haddock documentation for [http://hackage.haskell.org/packages/archive/wx/latest/doc/html/Graphics-UI-WX-Events.html WX.Events] and the lower level [http://hackage.haskell.org/packages/archive/wxcore/latest/doc/html/Graphics-UI-WXCore-Events.html WXCore.Events]
 
 
Since wxHaskell is based on an object-oriented framework, we also encode inheritance. The extra type parameter of objects encodes the inheritance relationship. When the parameter of an object is unit <tt>()</tt>, it denotes an object of that exact class. When the parameter is a type variable <tt>a</tt>, it denotes any object that is instance of that class. For example, both the <tt>frame</tt> and <tt>button</tt> functions return precisely a frame or button and use a <tt>()</tt> type parameter. However, the <tt>text</tt> attribute applies to any kind of window, including frames and buttons, and has a <tt>Window a</tt> as its argument. We can now use the <tt>text</tt> attribute for example for both frames and buttons. In wxHaskell, this works since a <tt>Frame&#160;()</tt> is actually a type synonym for <tt>Window&#160;(CFrame&#160;())</tt> and can thus be passed where a <tt>Window a</tt> is expected. The same hold for a <tt>Button ()</tt> that is a synonym for <tt>Control&#160;(CButton&#160;())</tt> that is again a synonym for <tt>Window&#160;(CControl&#160;(CButton&#160;()))</tt>.
 
 
==== Layout ====
 
 
The layout of a window is specified through the <tt>layout</tt> attribute. The layout of the current program is rather terse and we will spice it up by letting the button float in the center when the window is resized. This is also a good opportunity to add a small margin around the button.
 
 
[[Image:quick2-win.png|Hello world sample]]
 
<pre>set f [layout := margin 10 (floatCentre (widget quit))]</pre>
 
We can also add a text label above the button that is also centered. The argument of <tt>column</tt> specifies the amount of space between the items.
 
 
[[Image:quick3-win.png|Hello world sample]]
 
<pre>set f [layout := margin 10 (column 5 [floatCentre (label &quot;Hello&quot;)
 
,floatCentre (widget quit)
 
] )]</pre>
 
You can find out more about layout in the documentation for the [http://wxhaskell.sourceforge.net/doc/Graphics-UI-WXCore-Layout.html WXCore.Layout] module.
 
 
=== Bouncing balls ===
 
 
It is time for a more fun program that our Hello sample. We will write a program that lets us bounce balls on the screen!
 
 
[[Image:bouncingballs-win.png|Bouncing balls on Windows 2000]] [[Image:bouncingballs-gtk.png|Bouncing balls on Gentoo Linux with GTK and KDE]] [[Image:bouncingballs-mac.png|Bouncing balls on MacOS X (Panther)]] [[Image:bouncingballs-rh-gtk.png|Bouncing balls on Red Hat Linux (Fedora)]]
 
 
Note that the bouncing balls window is not resizeable, with the maximize box greyed out on windows. First we look at the main function in our program – <tt>ballsFrame</tt>:
 
 
<pre>module Main where
 
import Graphics.UI.WX
 
 
-- constants: radius of the ball, and the maximal x and y coordinates
 
radius, maxX, maxY :: Int
 
maxY = 300
 
maxX = 300
 
radius = 10
 
 
-- the max. height is at most max. y minus the radius of a ball.
 
maxH :: Int
 
maxH = maxY - radius
 
 
--the main function
 
main = start ballsFrame
 
 
ballsFrame
 
= do -- a list of balls, where each ball is represented
 
-- by a list of all future positions.
 
vballs &lt;- varCreate []
 
 
-- create a non-user-resizable top-level (orphan) frame.
 
f &lt;- frameFixed [text := &quot;Bouncing balls&quot;]
 
 
-- create a panel to draw in.
 
p &lt;- panel f [on paint := paintBalls vballs]
 
 
-- create a timer that updates the ball positions
 
t &lt;- timer f [interval := 20, on command := nextBalls vballs p]
 
 
-- react on user input
 
set p [on click&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160; := dropBall vballs p&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160; -- drop ball
 
,on clickRight&#160;&#160;&#160; := (\pt -&gt; ballsFrame)&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160;&#160; -- new window
 
,on (charKey 'p') := set t [enabled&#160;&#160; :~ not]&#160;&#160;&#160;&#160;&#160;&#160;&#160; -- pause
 
,on (charKey '-') := set t [interval :~ \i -&gt; i*2]&#160; -- increase interval
 
,on (charKey '+') := set t [interval :~ \i -&gt; max 1 (i `div` 2)]
 
]
 
 
-- put the panel in the frame, with a minimal size
 
set f [layout := minsize (sz maxX maxY) $ widget p]
 
where
 
...</pre>
 
Unlike more functional GUI libraries, wxHaskell does not provide a model for state management and uses simple mutable variables to communicate state across different event handlers. (Note: this is a concious design decision – as functional GUI interfaces are still very much a research area, we want to provide a full fledged GUI library using simple IO first, than try to build good functional interfaces on top of that). The state of the bouncing balls demo is a list of balls. Each ball is represented as a list of all its future heights. At the start of the program the list is empty (<tt>varCreate []</tt>).
 
 
Next, we use <tt>fixedFrame</tt> to create a non-resizeable window frame. A panel is created to paint the balls on and its <tt>paint</tt> handler paints the current balls in the panel. (Note: a panel has nothing to do with a Java panel: it is a widget that is normally used to place controls in as it manages control navigation keys like tab).
 
 
To animate the balls, we install a timer that advances all the balls on each timer tick and causes the panel to repaint the balls. We also install event handlers that react on the user: a mouse click causes a new ball to drop, a right click opens another frame (!), a <tt>p</tt>-key pauses the balls, and <tt>+/-</tt> increase/decrease the speed of the balls. Note how the operator <tt>(:~)</tt> applies a function to an attribute value instead of assigning one. Thus, the expression <tt>(set t [enabled :~ not])</tt> flips the enabled state of the timer.
 
 
Finally, we specify the layout of the frame, using <tt>minsize</tt> to specifiy the minimal size of the panel and thus the size of the frame as it is not resizeable.
 
 
==== Painting ====
 
 
Let us look at the paint event handler of the panel:
 
 
<pre> -- paint the balls
 
paintBalls :: Var [[Point]] -&gt; DC a -&gt; Rect -&gt; IO ()
 
paintBalls vballs dc viewArea
 
= do balls &lt;- varGet vballs
 
set dc [brushColor := red, brushKind := BrushSolid]
 
mapM_ (drawBall dc) [p | (p:ps) &lt;- balls]
 
 
drawBall dc pt
 
= circle dc pt radius []</pre>
 
A paint event handler gets two arguments: a device context (<tt>DC</tt>) to draw on and a rectangle that specifies the coordinates of the viewing area. We have supplied the first argument ourselves when setting the event handler, namely the mutable variable that holds the list of all balls.
 
 
As said, a single ball is represented as a list of all its future positions. When painting the current balls, we simple extract the head positions of all balls and draw them using <tt>drawBall</tt>. Drawing combinators like <tt>circle</tt> draw using the current ''pen'', ''brush'', and ''font'' of the device context. By default, a brush is transparent so we set it to a solid red brush before drawing the circles. Note that this is an optimization, we could have achieved the same effect by setting it for each circle individually: <tt>circle dc pt radius [brushKind := BrushSolid, brushColor := red]</tt>. You can read more about drawing in the documentation of the [http://hackage.haskell.org/packages/archive/wx/latest/doc/html/Graphics-UI-WX-Draw.html WX.Draw] module.
 
 
==== Bouncing ====
 
 
The timer event handler uses <tt>nextBalls</tt> to advance all the balls to their next postion.
 
 
<pre> -- advance all the balls to their next position
 
nextBalls :: Var [[Point]] -&gt; Panel () -&gt; IO ()
 
nextBalls vballs p
 
= do varUpdate vballs (filter (not.null) . map (drop 1))
 
repaint p</pre>
 
Updating the positions simply consists of dropping all initial positions and filtering out all empty lists. The function <tt>repaint</tt> is used to invoke the paint event handler of the panel.
 
 
When a users clicks on the panel, a new ball is created in <tt>dropBall</tt>.
 
 
<pre> -- drop a new ball, gets mouse position as last argument
 
dropBall :: Var [[Point]] -&gt; Panel () -&gt; Point -&gt; IO ()
 
dropBall vballs p pt
 
= do varUpdate vballs (bouncing pt:)
 
repaint p
 
 
-- calculate all future positions
 
bouncing (Point x y)
 
= map (\h -&gt; Point x (maxH-h)) (bounce (maxH-y) 0)
 
 
-- calculate all future heights
 
bounce h v
 
| h &lt;= 0 &amp;&amp; v == 0 = replicate 20 0 -- keep still for 20 frames
 
| h &lt;= 0 &amp;&amp; v&#160; &lt; 0 = bounce 0 ((-v)-2)
 
| otherwise&#160;&#160;&#160;&#160;&#160;&#160;&#160; = h : bounce (h+v) (v-1)</pre>
 
We prepend a new list of ball positions to the existing list using the <tt>varUpdate</tt> function and we repaint the panel. The new list of positions is calculated with the <tt>bouncing</tt> function that takes the position of the mouse pointer as its argument. This function uses the <tt>bounce</tt> function to calculate all future heights given an initial height and speed. Each time the ball touches the ground, it loses 2 units of speed.
 
 
Hopefully this sample inspires you to write more interesting GUI's. Don't forget to look at the samples provided with the wxHaskell documentation.
 
 
[[Category:wxHaskell|Quick start]]
 

Revision as of 14:10, 6 February 2021