[GUI] Re: Gtk and Object I/O

Daan Leijen daanleijen@xs4all.nl
Fri, 24 Jan 2003 15:21:31 +0100


Dear gui list members,

The discussions on this list seem to diverge rather quickly.
Most importantly for the Haskell community right now is the
short-term availability of a *some* middle-ground portable gui
library: worse is better.

In the past months, Krasimir has worked very hard on creating
a low-level portable C interface that is implemented for
both GTK and Windows -- an amazing piece of work, thanks Krasimir!
In the past weeks, I have put a small Haskell marshalling layer on
top of the C interface -- the resulting library is called "Graphics.UI.Port"
(and is available (and haddock documented) from the HToolkit sourceforge
cvs.)

Allthough it is not 'complete', the interface is already fairly substantial
and
I think it embodies a great *concrete* proposal for a low-level, portable
GUI interface in Haskell. I really hope that people will give this a good
look
and I think we should seriously consider adapting this interface as the
new standard low-level portable gui interface for Haskell.

Haddock documentation can be viewed online at:
http://www.cs.uu.nl/~daan/doc/port



------------
Furthermore, on top of the Port library, I have written a middle-ground
GUI library to test the suitability of the Port interface. This library is
called
"Graphics.UI.GIO", for graphical IO. The name is not without reason,
the library is middle-ground and all operations are still in the IO monad,
there is no explicit structure for modelling state.

The interface is extremely similar to Yahu and TkGofer
(see http://www.cs.chalmers.se/Cs/Grundutb/Kurser/afp/yahu.html )
and I have attached some (working!) source code of the famous bouncing
balls demo to give an impression.

GIO is still just a skeleton and not yet public, but again, it may be the
basis
of a concrete proposal towards a middle ground GUI library. On top of this,
people
can build their own fancy interfaces, like FranTk, Fruit, or even ObjectIO.
(see "Structuring graphical paradigms in TkGofer").

Haddock documentation can be viewed online at:
http://www.cs.uu.nl/~daan/doc/gio

All the best,
    Daan.


------------------
module Main where

import Graphics.UI.GIO

main
  = start balls

balls
  = do vballs <- newVar []
          w <- window [title =: "Bouncing balls", resizeable =: False, view
=: sz maxX maxY]
          set w [ on paint =: paintBalls  vballs
                   , on click =: dropBall w vballs ]
          timer [interval =: 20, on command =: nextBalls w vballs]
  where
    nextBalls w vballs
      = do updateVar vballs (filter (not.null) . map (drop 1))
              repaint w

    dropBall w vballs pt
      = do updateVar vballs (bouncing pt:)
              repaint w

    bouncing (Point x y)
      = map (\h -> Point x (maxH-h)) (bounce (maxH-y) 0)

    bounce h v
      | h <= 0 && v == 0     = []
      | h <= 0 && v  < 0     = bounce 0 ((-v)-2)
      | otherwise            = h : bounce (h+v) (v-1)


    paintBalls vballs can updframe updareas
      = do box updframe [color =: lightgrey] can
              balls <- getVar vballs
              mapM_ (drawBall can) (map head (filter (not.null) balls))

    drawBall can pt
      = do oval pt radius radius [color =: red] can
               ellipse pt radius radius [] can


-- radius 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