It is possible to draw quite complex figures in Gtk2Hs, on screen and in several file formats, using the Cairo drawing library. Drawing in Gtk2Hs is not very different from drawing in original Cairo, though that subject is large enough to merit its own tutorials.
See the Cairo Documentation Site for that.
Drawing to the screen or in portable network graphics (png), portable document format (pdf), postscript (ps) or scaleable vector graphics (svg) formats of any Cairo drawing uses some special syntax in Gtk2Hs. The goal of this appendix is to explain what basic functions you need.
import Graphics.Rendering.Cairo
.
Then the following function defines an actual drawing:
myDraw :: Render () myDraw = do setSourceRGB 1 1 0 setLineWidth 5 moveTo 120 60 lineTo 60 110 lineTo 180 110 closePath stroke
The type of this function is Render ()
and from the do notation you can gather
that Render
is a monad. Note that this is not the IO
monad, which is
used in Graphics.UI.Gtk
. The figure, a triangle, is defined by the moveTo,
lineTo and closePath
functions, which do what the names suggest. They do not, however,
draw anything, but rather define a path, which is to be followed. The actual drawing of this path is done by the
stroke
function. First, however, the color of the lines and their width must
be specified.
Now this figure can be drawn. For this we need a blank widget, with DrawingArea
type.
However, you don't draw on this widget itself, the canvas
in the example below,
but on its DrawWindow
. To get it you use:
widgetGetDrawWindow :: WidgetClass widget => widget -> IO DrawWindowor, alteratively, the simpler:
drawingAreaGetDrawWindow :: DrawingArea -> IO DrawWindow
Now you can use:
renderWithDrawable :: DrawableClass drawable => drawable -> Render a -> IO a
But this drawing must be executed in response to an event. One possibility would be
an onButtonPress
event as used in Chapter 6.2 with the Event Box. This actually works.
Each time the window is resized the drawing disappears, and it is drawn again when you click
the button. There is another event, however, the Expose
event, which sends a signal
each time the window is resized or redrawn on the screen. This fits what is required, so we use:
onExpose canvas (\x -> do renderWithDrawable drawin myDraw return (eventSent x))
This is how it looks:
A frame has also been included, for visual effect, but this is inessential.
But note that the widgetShowAll
function appears before the
widgetGetDrawWindow
function in the code below. This is required because only a visible
window can be used to draw on!
import Graphics.UI.Gtk import Graphics.Rendering.Cairo main :: IO () main= do initGUI window <- windowNew set window [windowTitle := "Hello Cairo", windowDefaultWidth := 300, windowDefaultHeight := 200, containerBorderWidth := 30 ] frame <- frameNew containerAdd window frame canvas <- drawingAreaNew containerAdd frame canvas widgetModifyBg canvas StateNormal (Color 65535 65535 65535) widgetShowAll window drawin <- widgetGetDrawWindow canvas onExpose canvas (\x -> do renderWithDrawable drawin myDraw return (eventSent x)) onDestroy window mainQuit mainGUI myDraw :: Render () myDraw = do setSourceRGB 1 1 0 setLineWidth 5 moveTo 120 60 lineTo 60 110 lineTo 180 110 closePath stroke
This example does not really do what we want because, though the figure is redrawn, it does not resize with the main window. To do this we need:
myDraw :: Double -> Double -> Render () myDraw w h = do setSourceRGB 1 1 1 paint setSourceRGB 1 1 0 setLineWidth 5 moveTo (0.5 * w) (0.43 * h) lineTo (0.33 * w) (0.71 * h) lineTo (0.66 * w) (0.71 * h) closePath stroke
Now the drawing will always fit the borders defined by the parameters. We've also
set the background color with the paint function, instead of widgetModify
.
The paint
function paints the current source everywhere within the current
clip region. Note that setSourceRGB
not only takes a Double
between 0 and 1 as its parameters instead of Int
values between 0 and 65535,
but also 'lives' within the Render
monad instead of the IO
monad.
To draw the resizable figure, we need to get the size of the drawing area each time this changes.
widgetGetSize :: WidgetClass widget => widget -> IO (Int, Int)
So the code snippet to draw becomes:
onExpose canvas (\x -> do (w,h) <- widgetGetSize canvas drw <- widgetGetDrawWindow canvas renderWithDrawable drw (myDraw (fromIntegral w) (fromIntegral h)) return (eventSent x))
Because the rest of the code is the same as before we won't list it, but this is the result of a resizing to the right:
Another drawing example, this one taken from the general Cairo Tutorial is:
This is the listing:
import Graphics.UI.Gtk hiding (fill) import Graphics.Rendering.Cairo main :: IO () main= do initGUI window <- windowNew set window [windowTitle := "Hello Cairo 4", windowDefaultWidth := 300, windowDefaultHeight := 200, containerBorderWidth := 15 ] frame <- frameNew containerAdd window frame canvas <- drawingAreaNew containerAdd frame canvas widgetShowAll window onExpose canvas (\x -> do (w,h) <- widgetGetSize canvas drawin <- widgetGetDrawWindow canvas renderWithDrawable drawin (myDraw (fromIntegral w)(fromIntegral h)) return (eventSent x)) onDestroy window mainQuit mainGUI myDraw :: Double -> Double -> Render () myDraw w h = do setSourceRGB 1 1 1 paint setSourceRGB 0 0 0 moveTo 0 0 lineTo w h moveTo w 0 lineTo 0 h setLineWidth (0.1 * (h + w)) stroke rectangle 0 0 (0.5 * w) (0.5 * h) setSourceRGBA 1 0 0 0.8 fill rectangle 0 (0.5 * h) (0.5 * w) (0.5 * h) setSourceRGBA 0 1 0 0.6 fill rectangle (0.5 * w) 0 (0.5 * w) (0.5 * h) setSourceRGBA 0 0 1 0.4 fill
Note that this is just like the previous example, except for the actual drawing. This introduces
setSourceRGBA
which sets not just the color but also the transparency, as a
measure between 0 and 1. The example also uses a rectangle
and a method
fill
which fills closed figures with the specified color and transparancy.
Note: Because of a naming conflict with an older
Gtk2Hs drawing library you must either hide fill
in the Graphics.UI.Gtk import
statement or use the full name Graphics.Rendering.Cairo.fill
.
It's very easy to save a drawing in png, pdf, ps or svg formats. 'Save' is perhaps not the correct expression, since each different format involves its own rendering. The function is:
renderWith:: MonadIO m => Surface -> Render a -> m aThe
Surface
is that on which the drawing appears. In these cases this is not the screen
but something you'll have to provide yourself. There are four different functions, one for each type.
withImageSurface :: Format -- format of pixels in the surface to create -> Int -- width of the surface, in pixels -> Int -- height of the surface, in pixels -> (Surface -> IO a) -- an action that may use the surface. The surface is only valid within in this action. -> IO a
This is used for portable network graphics (png) files. The Format
data type
has four possible constructors, FormatARGB32, FormatRGB24, FormatA8, FormatA1
.
In the example below we use the first. The action that takes a Surface
as its
argument will usually be the renderWith
function followed by a function to
write to a file. For the png format this would be the function:
surfaceWriteToPNG :: Surface -- a Surface -> FilePath -- the name of a file to write to -> IO ()
So, the recipe to write a drawing to a file in png format would be:
withImageSurface FormatARGB32 pnw pnh (\srf -> do renderWith srf (myDraw (fromIntegral pnw) (fromIntegral pnh)) surfaceWriteToPNG srf "myDraw.png")
where pnw
and pnh
are the width and the height in type Int
.
To save a drawing in pdf format you use:
withPDFSurface :: FilePath -- a filename for the PDF output (must be writable) -> Double -- width of the surface, in points (1 point == 1/72.0 inch) -> Double -- height of the surface, in points (1 point == 1/72.0 inch) -> (Surface -> IO a) -- an action that may use the surface. The surface is only valid within in this action. -> IO a
This function takes different parameters than the previous on, though it is very similar. The recipe to save is now:
withPDFSurface "myDraw.pdf" pdw pdh (\s -> renderWith s $ do myDraw pdw pdh showPage )
Note the showPage
function. Without it the program will compile, and even produce a .pdf
file, but this cannot be read correctly by a pdf reader. The API documentation states the width and height
are in points (and type Double
), so you'll have to check how this works out in practice.
To save a postscript file:
withPSSurface :: FilePath -- a filename for the PS output (must be writable) -> Double -- width of the surface, in points (1 point == 1/72.0 inch) -> Double -- height of the surface, in points (1 point == 1/72.0 inch) -> (Surface -> IO a) -- an action that may use the surface. The surface is only valid within in this action. -> IO a
To save you could use the same 'recipe' as above, or the shorter notation:
withPSSurface "myDraw.ps" psw psh (flip renderWith (myDraw psw psh >> showPage))
Finally, to save in scaleable vector graphics format, use the same syntax, but with
withSVGSurface
. So this would be:
withSVGSurface "myDraw.svg" pgw pgh (flip renderWith $ myDraw pgw pgh >> showPage)
An example that saves the last drawing shown above in all four formats (with different sizes) is:
import Graphics.UI.Gtk hiding (fill) import Graphics.Rendering.Cairo main :: IO () main= do initGUI window <- windowNew set window [windowTitle := "Save as...", windowDefaultWidth := 300, windowDefaultHeight := 200] let pnw = 300 pnh = 200 withImageSurface FormatARGB32 pnw pnh (\srf -> do renderWith srf (myDraw (fromIntegral pnw) (fromIntegral pnh)) surfaceWriteToPNG srf "myDraw.png") let pdw = 720 pdh = 720 withPDFSurface "myDraw.pdf" pdw pdh (\s -> renderWith s $ do myDraw pdw pdh showPage ) let psw = 360 psh = 540 withPSSurface "myDraw.ps" psw psh (flip renderWith (myDraw psw psh >> showPage)) let pgw = 180 pgh = 360 withSVGSurface "myDraw.svg" pgw pgh (flip renderWith $ myDraw pgw pgh >> showPage) putStrLn "Press any key to quit..." onKeyPress window (\x -> do widgetDestroy window return (eventSent x)) widgetShowAll window onDestroy window mainQuit mainGUI myDraw :: Double -> Double -> Render () myDraw w h = do setSourceRGB 1 1 1 paint setSourceRGB 0 0 0 moveTo 0 0 lineTo w h moveTo w 0 lineTo 0 h setLineWidth (0.1 * (h + w)) stroke rectangle 0 0 (0.5 * w) (0.5 * h) setSourceRGBA 1 0 0 0.8 fill rectangle 0 (0.5 * h) (0.5 * w) (0.5 * h) setSourceRGBA 0 1 0 0.6 fill rectangle (0.5 * w) 0 (0.5 * w) (0.5 * h) setSourceRGBA 0 0 1 0.4 fill
Note: Please see the Graphics.Rendering.Cairo API documentation and the general Cairo tutorials and examples for more advanced uses. The Gtk2Hs distribution also comes with several interesting demonstration examples.