Jump to content
Main menu
Main menu
move to sidebar
hide
Navigation
Haskell
Wiki community
Recent changes
Random page
HaskellWiki
Search
Search
Create account
Log in
Personal tools
Create account
Log in
Pages for logged out editors
learn more
Contributions
Talk
Editing
Cn/WxHaskell/Quick start
(section)
Page
Discussion
English
Read
Edit
View history
Tools
Tools
move to sidebar
hide
Actions
Read
Edit
View history
General
What links here
Related changes
Special pages
Page information
Warning:
You are not logged in. Your IP address will be publicly visible if you make any edits. If you
log in
or
create an account
, your edits will be attributed to your username, along with other benefits.
Anti-spam check. Do
not
fill this in!
=== 弹力球游戏 === 现在是时候做一个更好玩的程序了。我们将写一个程序,它可以让我们在屏幕上玩弹力球! [[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)]] 注意这个弹力球游戏的窗口不能缩放,因此最大化按钮是灰的。首先我们来看程序的主函数 – 《tt>ballsFrame</tt>: <pre>module Main where import Graphics.UI.WX -- 常量定义,球的半径和窗口的长宽。 radius, maxX, maxY :: Int maxY = 300 maxX = 300 radius = 10 -- 球的最大高度,实际上是 maxH 减去球的半径。 maxH :: Int maxH = maxY - radius -- 主函数 main = start ballsFrame ballsFrame = do -- 球的列表,每个球由球将来的运动轨迹上的点来描述。 vballs <- varCreate [] -- 创建一个用户不能缩放大小的顶级窗口框架 f <- frameFixed [text := "Bouncing balls"] -- 创建用来画图的面板 p <- panel f [on paint := paintBalls vballs] -- 创建一个定时器,用来更新球的位置 t <- timer f [interval := 20, on command := nextBalls vballs p] -- 和用户的交互 set p [on click         := dropBall vballs p              -- drop ball ,on clickRight    := (\pt -> ballsFrame)            -- new window ,on (charKey 'p') := set t [enabled   :~ not]        -- pause ,on (charKey '-') := set t [interval :~ \i -> i*2]  -- increase interval ,on (charKey '+') := set t [interval :~ \i -> max 1 (i `div` 2)] ] -- 把面板放到框架中去,并且最小化。 set f [layout := minsize (sz maxX maxY) $ widget p] where ...</pre> 和大多数函数式 GUI 库不同,wxHaskell 不提供状态管理的机制,用户不能用简单的变量来在多个不同的事件之间传递或保持状态。(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]] -> DC a -> Rect -> IO () paintBalls vballs dc viewArea = do balls <- varGet vballs set dc [brushColor := red, brushKind := BrushSolid] mapM_ (drawBall dc) [p | (p:ps) <- 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]] -> Panel () -> 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]] -> Panel () -> Point -> IO () dropBall vballs p pt = do varUpdate vballs (bouncing pt:) repaint p -- calculate all future positions bouncing (Point x y) = map (\h -> Point x (maxH-h)) (bounce (maxH-y) 0) -- calculate all future heights bounce h v | h <= 0 && v == 0 = replicate 20 0 -- keep still for 20 frames | h <= 0 && v  < 0 = bounce 0 ((-v)-2) | otherwise        = 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]] [[Category:Chinese]]
Summary:
Please note that all contributions to HaskellWiki are considered to be released under simple permissive license (see
HaskellWiki:Copyrights
for details). If you don't want your writing to be edited mercilessly and redistributed at will, then don't submit it here.
You are also promising us that you wrote this yourself, or copied it from a public domain or similar free resource.
DO NOT SUBMIT COPYRIGHTED WORK WITHOUT PERMISSION!
Cancel
Editing help
(opens in new window)
Toggle limited content width