X window programming in Haskell

From HaskellWiki
Revision as of 17:44, 19 July 2007 by AndreaRossato (talk | contribs) (added the color management section)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

Writing an X Application With Haskell Xlib Bindings

This tutorial is a side product of the research and the learning experience of writing a status bar for the XMonad Window Manager, the first WM written in Haskell.

It will show you how to write a simple X application using the low level Xlib library. The goal is to write a simple text base clock, that will display the system time, to be run on top of every other applications, like a status bar.

While the application is fairly simple, still it will require us to get to know quite a lot of the details that must be taken into account when writing a properly working X application.

Obviously some understanding of X and Xlib is required.

These are some links that can be used as reference:

This tutorial is dedicated to the intermediate Haskell coder. While I will try to write the simplest code I can (probably it will even look the dumbest, but that's me), I'm not going into much details about the Haskell part.

What are we going to learn:

  • how to create a window and set, or change, its attributes;
  • how to draw in that window, specifically some text, with some properties, like fonts or colors;
  • how to properly update the window;
  • how to handle events, like a mouse button press.

In order to compile the following code examples you need at least:

  • X11, the Haskell binding to the X11 graphics library.
  • X11-extras: will be required in some examples. This library provides missing bindings to the X11 graphics library and is actively developed by Spencer Janssen at the time of this writing. Some functions needed in this tutorial can be found only in the darcs repository of X11-extras: http://darcs.haskell.org/~sjanssen/X11-extras. Read carefully the README before installing.


Hello World

Let's start from the usual simple "Hello World"

module Main where
import Graphics.X11.Xlib
import System.Exit (exitWith, ExitCode(..))
import Control.Concurrent (threadDelay)

main :: IO ()
main =
    do dpy <- openDisplay ""
       let dflt = defaultScreen dpy
           border =  blackPixel dpy dflt
           background = whitePixel dpy dflt
       rootw  <- rootWindow dpy dflt
       win <- createSimpleWindow dpy rootw 0 0 100 100 1 border background
       setTextProperty dpy win "Hello World" wM_NAME 
       mapWindow dpy win
       sync dpy False
       threadDelay (10 * 1000000)
       exitWith ExitSuccess

The first function, openDisplay, is the interface to the Xlib function XOpenDisplay(), and opens a connection to the X sever that controls a display. The connection is returned and bound to dpy. By applying defaultScreen, the interface to XDefaultScreen, we get the root window. We need it in order to set out parent window in the most important function of the above code: createSimpleWindow, the interface to XCreateSimpleWindow.

This function takes, as arguments: the display, the parent window of the window to be created, the x position, the y position, the width, the height, the border width, the border pixel and the background pixel.

The x and y positions are relative to the upper left corner of the parent window's inside borders.

In order to retrieve the values of the black and white pixels for that specific screen, we use two specific functions: blackPixel, the interface to the X11 library function BlackPixel, and whitePixel, the interface to the X11 library function WhitePixel

The function createSimpleWindow will return the window ID and, with this ID, we can start manipulating our newly created window, as we do, in the above code, with the function setTextProperty, interface to the X11 library function XSetTextProperty().

This function is needed, in our code, to set the window's name, that your window manager will display on some decoration attached to the window (other window managers will not display anything, for instance a tiling WM like XMonad)

To set the window's name we need to manipulate the XTextProperty structure.

Properties, such as the XTextProperty, have a string name and a numerical identifier called an atom. An atom is an ID that uniquely identifies a particular property. Property name strings are typically all upper case - with the first letter in low case when translated into Haskell - with words separated by underscores. In our example we had to set the WM_NAME property to "Hello World".

Creating and manipulating a window is just the first step to have a new window displayed. In order for the window to become visible we must map it with mapWindow, the interface to the X11 library function XMapWindow(). This will make the window visible.

Xlib will not send requests and calls to the Xserver immediately, but will buffer them and send the full buffer when some given conditions are met.

One way to force the flushing of the output buffer is to call sync, the interface to the X11 library function XSync(), which takes 2 arguments: the connection (dpy) and a Boolean value that indicates whether XSync() must discard all events on the event queue.

After that the Xserver will eventually display our window.

The rest of the above example does nothing else but blocking the program execution for 10 seconds (to let you stare at your newly created window) and then will exit.

Window's Attributes

Even though in our "Hello World" example we set the window's dimension, we have no assurance that the Window Manager will respect our decision.

XMonad, for instance, will just create a window with the dimensions needed to fill its tiled screen, no matter what you set in createSimpleWindow.

But we decided to write a small clock that will behave as a status bar, that is to say, we want to create a window that will not be managed by a Window Manager.

In order to achieve this result we need to start dealing with window's attributes.

There are two ways of dealing with window's attributes: the first is to set them at window's creation time, but in that case createSimpleWindow is not powerful enough.

The second way is to change window's attributes after the window's has been created. This second approach is not implemented X11 but has been implemented in the darcs version of X11-extras.

Setting Window's Attribute at Creation Time

In order to set window's attributes at creation time, the window must be created with createWindow, the interface to the X11 library function XCreateWindow().

The type signature of this function is quite long:

createWindow :: Display -> Window 
                -> Position -> Position 
                -> Dimension -> Dimension 
                -> CInt 
                -> CInt 
                -> WindowClass 
                -> Visual 
                -> AttributeMask 
                -> Ptr SetWindowAttributes 
                -> IO Window

That is to say:

  • the connection and the parent window
  • the x and y position (origins in the upper left corner of the inside border of the parent window)
  • width and height
  • border width
  • depth of screen
  • the window's class
  • the visual
  • the attribute mask
  • and the pointer to the XSetWindowAttributes foreign C structure.

This last one gives you an idea of the type of operation we must do in order to create a window (createSimpleWindow is just a wrapper around this more complicated createWindow, with some default arguments): we need a function to allocate some memory for the creation of the foreign C structure, and then manipulate this foreign structure from within this function.

The needed function is allocaSetWindowAttributes, whose type indeed is:

allocaSetWindowAttributes :: (Ptr SetWindowAttributes -> IO a) -> IO a

allocaSetWindowAttributes will take a function which takes the pointer to the foreign structure as its argument. This function will perform an IO action that is the action returned by allocaSetWindowAttributes.

In our case allocaSetWindowAttributes will take a function that will use createWindow to return the new window.

So, we will need to use createWindow inside allocaSetWindowAttributes. We will soon see how. But first let's analyze the other arguments of createWindow.

The display, the parent window, the coordinates and dimensions are the same as with createSimpleWindow. But now we must specify the depth of the screen, the window's class, the visual and the attribute mask. We also need to manipulate the XSetWindowAttribute after its creation by allocaSetWindowAttributes, before calling createWindow.

«The depth is the number of bits available for each pixel to represent color (or gray scales). The visual represents the way pixel values are translated to produce color or monochrome output on the monitor.»( see http://www.sbin.org/doc/Xlib/chapt_02.html)

For the depth we are going to use defaultDepthOfScreen, interface to the X11 library function XDefaultDepthOfScreen(), to retrieve the default screen depth.

For the visual we are going to use defaultVisualOfScreen, interface to the X11 library function DefaultVisualOfScreen.

The WindowClass can either be copyFromParent, inputOutput, or inputOnly. In the first case the class is copied from the class of the parent window. An inputOnly window can only be used for receiving input events. In our code we are going to use inputOutput windows, windows that can receive input events and that can also be used to display some output.

The attributeMask «specifies which window attributes are defined in the attributes argument. This mask is the bitwise inclusive OR of the valid attribute mask bits. If value mask is zero, the attributes are ignored and are not referenced.» (see http://www.tronche.com/gui/x/xlib/window/XCreateWindow.html).

In other words, in order to set more then one attribute, you need to pass a value mask such as:

attrmask = cWOverrideRedirect .|. cWBorderPixel .|. cWBackPixel .|. etc ...

and set each of this attributes within allocaSetWindowAttributes with specific attributes setting functions.

Among these functions the one we need: set_override_redirect, whose type is:

set_override_redirect :: Ptr SetWindowAttributes -> Bool -> IO ()

This function takes the pointer to the XSetWindowAttributes structure and the flag to be set (True or False).

For the list of avaliable attributes see the AttributeMask type defnition.

For their meaning see the XSetWindowAttributes structure reference.

Now, our goal was to create a window that the Window Manager is going to ignore, and in order to do that all we need to set the attribute CWOverrideRedirect to True. And now we know how to do it.

Ok, it's time to introduce our function to create new windows with the CWOverrideRedirect set to True

mkUnmanagedWindow :: Display
                  -> Screen
                  -> Window
                  -> Position
                  -> Position
                  -> Dimension
                  -> Dimension
                  -> IO Window
mkUnmanagedWindow dpy scr rw x y w h = do
  let visual = defaultVisualOfScreen scr
      attrmask = cWOverrideRedirect
  win <- allocaSetWindowAttributes $ 
         \attributes -> do
           set_override_redirect attributes True
           createWindow dpy rw x y w h 0 (defaultDepthOfScreen scr) 
                        inputOutput visual attrmask attributes                                
  return win

Like simpleCreateWindow, our function is a wrapper around createWindow, but this time we are manually setting the CWOverrideRedirect flag.

As you see our function, unlike createSimpleWindow, does not have, among its arguments, the background and the border pixels. This colors can be set, for windows created with createWindow, using the attribute mask, and setting CWBackPixel and CWBorderPixel with the needed functions: set_background_pixel and set_border_pixel.

By the way, setting the border color with this version of mkUnmanagedWindow is actually useless since the border width is set to zero. In the next example we will set it to 1.

Our function needs also the screen now, since we have to retrieve the default depth and visual.

We can now rewrite our initial code using the new function now.

module Main where
import Data.Bits
import Graphics.X11.Xlib
import System.Exit (exitWith, ExitCode(..))
import Control.Concurrent (threadDelay)

main :: IO ()
main =
    do dpy <- openDisplay ""
       let dflt = defaultScreen dpy
           scr = defaultScreenOfDisplay dpy
       rootw  <- rootWindow dpy dflt
       win <- mkUnmanagedWindow dpy scr rootw 0 0 100 100
       setTextProperty dpy win "Hello World" wM_NAME 
       mapWindow dpy win
       sync dpy False
       threadDelay (10 * 1000000)
       exitWith ExitSuccess

mkUnmanagedWindow :: Display
                  -> Screen
                  -> Window
                  -> Position
                  -> Position
                  -> Dimension
                  -> Dimension
                  -> IO Window
mkUnmanagedWindow dpy scr rw x y w h = do
  let visual = defaultVisualOfScreen scr
      attrmask = cWOverrideRedirect .|. cWBorderPixel .|. cWBackPixel
  win <- allocaSetWindowAttributes $ 
         \attributes -> do
           set_override_redirect attributes True
           set_background_pixel attributes $ whitePixel dpy (defaultScreen dpy)
           set_border_pixel attributes $ blackPixel dpy (defaultScreen dpy)
           createWindow dpy rw x y w h 1 (defaultDepthOfScreen scr)
                        inputOutput visual attrmask attributes                                
  return win

Ok, let's give it a try. Did you see? Now the window will be placed in the specified x and y position, with the given dimensions. No Window Manager decorations, and so, no name displayed.

Changing an Existing Window's Attributes

This task requires XChangeWindowAttrbutes(), implemented only in the darcs version of X11-extras.

In order to change a window's attributes we just need the window ID in that specific X server, after that we need to unmap the window first, and then change its attributes with changeWindowAttributes, the interface to XChangeWindowAttrbutes() implemented by the darcs version of X11-extras.

Here's the code:

module Main where

import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
import System.Environment

usage :: String -> String
usage n = "Usage: " ++ n ++ " manage/unmanage windowID"

main :: IO ()
main = do
  args <- getArgs
  pn <- getProgName
  let (win,ac) = case args of
                   [] -> error $ usage pn
                   w -> case (w !!0) of 
                          "manage" -> (window, False)
                          "unmanage" ->  (window, True)
                          _ -> error $ usage pn
                       where window = case  (w !! 1) of 
                                               [] -> error $ usage pn
                                               w -> read w :: Window
  dpy <- openDisplay ""
  unmapWindow dpy win
  sync dpy False
  allocaSetWindowAttributes $
       \attributes -> do
         set_override_redirect attributes ac
         changeWindowAttributes dpy win cWOverrideRedirect attributes
  mapWindow dpy win
  sync dpy False

Save it as Unmanage.hs and compile with:

ghc --make Unmanage.hs -o unmanage

To use it you need to retrieve the window ID with the stand alone utility

xwininfo

Then you run the above code with:

unmanage unmanage/manage windowID

to set override_redirect to True or False.

Obviously the important part of the code is this:

  dpy <- openDisplay ""
  unmapWindow dpy win
  sync dpy False
  allocaSetWindowAttributes $
       \attributes -> do
         set_override_redirect attributes ac
         changeWindowAttributes dpy win cWOverrideRedirect attributes
  mapWindow dpy win
  sync dpy False

where we:

  1. connect to the X server
  2. unmap the window
  3. flush the output buffer to have the X server actually unmap the window
  4. change the attributes with the same procedure we used to set them when creating the window
  5. map the window again
  6. flush the output buffer to see the change take effect.

You can modify this program to change other window's attributes.

Colors and Color Depth

So far we have set the window background color as a window attribute. This is not the most convenient way to set the window background color: if need to change it we need to change the window's attribute, and we have seen that this task requires unmapping the window,flush the output, using changeWindowAttributes within changeWindowAttributes, remap the window and reflush the buffer. Moreover we need the darcs version of X11-extras...

In the following section we are gig to adopt a more efficient way of setting the window's background color: we will start drawing into the window. But first we must familiarize with colors and the way the X server deals with them.

So far we set the colors using some function: blackPixel and whitePixel. These functions take the display and the default screen and return respectively the pixel for the black and the white colors in that screen.

We have seen that a color is represented by a 32-bit unsigned integer, called a pixel value. The elements affecting the representation of a color are 1. the color depth; 2. the colormap, which is a table containing red, green, and blue intensity values; 3. the visual type.

All these elements are specific to a given piece of hardware, and so our X application must detect them in order to set colors appropriately for that given screen.

The approach we are going to use to accomplish this task is this: we are going to use named colors, or colors represented by RGB triple, such as "red", "yellow", or "#FFFFFF", etc; and we are going to translate these colors into the pixel values appropriate for the screen we are operating on.

In order to achieve our goal we are going to use the function allocNamedColor which is the interface to the X11 library function XAllocNamedColor().

The type signature of allocNamedColor is:

allocNamedColor :: Display -> Colormap -> String -> IO (Color, Color)

That is to say, given a display connection, a color map and a string - our color representation -, this function will return a tuple with the closest RGB values provided by the hardware and the exact RGB values. We will use the first for our future operation.

The Haskell Color data type has a field name we will use to retrieve the needed pixel value: color_pixel.

We can now write this helper function:

initColor :: Display -> String -> IO Pixel
initColor dpy color = do
  let colormap = defaultColormap dpy (defaultScreen dpy)
  (apros,real) <- allocNamedColor dpy colormap color
  return $ color_pixel apros

defaultColormap, the interface to the X11 library function XDefaultColormap(), requires the display and the screen, and returns the colormap for that screen.

We can now rewrite our example using this new approach.

module Main where
import Data.Bits
import Graphics.X11.Xlib
import System.Exit (exitWith, ExitCode(..))
import Control.Concurrent (threadDelay)

main :: IO ()
main =
    do dpy <- openDisplay ""
       let dflt = defaultScreen dpy
           scr = defaultScreenOfDisplay dpy
       rootw  <- rootWindow dpy dflt
       win <- mkUnmanagedWindow dpy scr rootw 0 0 100 100
       setTextProperty dpy win "Hello World" wM_NAME 
       mapWindow dpy win
       sync dpy False
       threadDelay (10 * 1000000)
       exitWith ExitSuccess

mkUnmanagedWindow :: Display
                  -> Screen
                  -> Window
                  -> Position
                  -> Position
                  -> Dimension
                  -> Dimension
                  -> IO Window
mkUnmanagedWindow dpy scr rw x y w h = do
  let visual = defaultVisualOfScreen scr
      attrmask = cWOverrideRedirect .|. cWBorderPixel .|. cWBackPixel
  background_color <- initColor dpy "red"
  border_color <- initColor dpy "black" 
  win <- allocaSetWindowAttributes $ 
         \attributes -> do
           set_override_redirect attributes True
           set_background_pixel attributes background_color
           set_border_pixel attributes border_color
           createWindow dpy rw x y w h 1 (defaultDepthOfScreen scr)
                        inputOutput visual attrmask attributes                                
  return win


initColor :: Display -> String -> IO Pixel
initColor dpy color = do
  let colormap = defaultColormap dpy (defaultScreen dpy)
  (apros,real) <- allocNamedColor dpy colormap color
  return $ color_pixel apros

Just give it a try. Now you can also experiment with different color. This approach will assure that our application will work no matter the color depth of the screen we are operating on.

Printing a String

To be continued ...

fonts, string length, colors, etc

Updating a Window

Pixmap and copyToWindow

Dealing with XEvents

Two approaches

- Andrea Rossato