Using WxGeneric

May 21, 2008

As I posted earlier AutoForms has been reimplement in a new library called WxGeneric. In this post we look at using WxGeneric from a purely practical perspective.

To understand this post you should already be familiar with Haskell and WxHaskell.

The short introduction to WxGeneric is that it is a library to generically construct WxHaskell widgets, by looking at the structure and names of types. If you want more background information, you should look at AutoForms, which is the library WxGeneric is based upon.

Installation

Before installing WxGeneric you must install the following dependencies:

The hard to install dependencies are GHC and WxHaskell (both of which you properly already got). The rest are installed as ordinary cabalized packages. See here for general information about installing cabalized packages.

Next download and install WxGeneric like a normal cabalized package.

Tuple example

We will start with a small example which converts a tuple (Int, String, Double) into a WxHaskell widget. Below you can see the example code. The code which is WxGeneric specific are italicized. The rest is ordinary WxHaskell code. The most interesting new function is genericWidget, which is used to construct widgets generically. This function takes two parameters – a frame and the value to turn into a widget. Also we have a new attribute called widgetValue, which can be used to get and set the value of a widget. The rest of the code is ordinary WxHaskell code:

module TupleExample where

import Graphics.UI.WxGeneric
import Graphics.UI.WX

main :: IO ()
main = start $
       do f <- frame [ text := "Tuple Example" ]
          p <- panel f []
          en <- genericWidget p (3 :: Int, "Hans", 5.5 :: Double)
          b <- button p [ text := "&Print tuple"
                        , on command := get en widgetValue >>= print ]
          set f [ layout := container p $ row 10 [ widget en, widget b ] ]

And the resulting GUI:

Tuple Example

Alarm example

In this example we will see how to convert a programmer defined data type into a widget. We have chosen an Alarm data type, which contains an alarm name and time of day (measured in minutes). The code:

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses
  , TemplateHaskell, UndecidableInstances #-}

module Alarm where

import Graphics.UI.WxGeneric
import Graphics.UI.SybWidget.MySYB

import Graphics.UI.WX
import Graphics.UI.WXCore

data Minutes = Minutes Int deriving (Show, Eq)
data Alarm = Alarm { name :: String
                   , timeOfDay :: Minutes
                   } deriving (Show, Eq)

$(derive [''Minutes,''Alarm])

instance WxGen Alarm
instance WxGen Minutes

main :: IO ()
main = start $
       do f <- frame [ text := "Alarm Example" ]
          p <- panel f []
          en <- genericWidget p (Alarm "My alarm" $ Minutes 117)
          b >= print ]
          set f [ layout := container p $ row 10 [ widget en, widget b ] ]

The three italicized lines are the boilerplate needed to convert the Alarm type into widgets. Derive is a Template Haskell function which derives instances for the two type classes Data and Typeable. In this case we derive instances for the two data types Minutes and Alarm. We also needs to specify that Alarm and Minutes can be turned into widgets. That is done by the two instance declarations. The rest is similar to the previous example.

And the resulting GUI:

Alarm Example

Specializing Alarm

Presenting time of day as minutes is not particular user friendly. However it is convenient to model it as such. Thus we would like to present the minutes differently to the user, as they are stored in the model. WxGeneric supports this:

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses
  , TemplateHaskell, UndecidableInstances #-}

module AlarmSpecialized where

import Graphics.UI.WxGeneric
import Graphics.UI.SybWidget.MySYB

import Graphics.UI.WX
import Graphics.UI.WXCore

import Control.Monad

data Minutes = Minutes Int deriving (Show, Eq)
data Alarm = Alarm { name :: String
                   , timeOfDay :: Minutes
                   } deriving (Show, Eq)
$(derive [''Minutes,''Alarm])

instance WxGen Alarm

instance WxGen Minutes where
    mkWid m' = toOuter (valuedCompose helper)
        where helper p = 
                  do changeVar <- varCreate (return ())
                     
                     hours   <- hslider p True 0 23 [ selection := fst $ minutes2Clock m' ]
                     minutes <- hslider p True 0 23 [ selection := snd $ minutes2Clock m' ]
                     
                     let setChangeVar x = do set hours   [ on command := x ]
                                             set minutes [ on command := x ]
                         lay = grid 10 10 [ [ label "Hours: ", fill $ widget hours ]
                                          , [ label "Minutes: ", fill $ widget minutes ] ]
                         getVal = liftM2 clock2Minutes (get hours selection) (get minutes selection)
                         setVal ys = do let (h, m) = minutes2Clock ys
                                        set hours [selection := h]
                                        set minutes [selection := m]
                     return ( lay, getVal, setVal
                            , varGet changeVar, setChangeVar
                            )
              minutes2Clock (Minutes m) = (m `div` 60, m `mod` 60)
              clock2Minutes h m         = Minutes (60*h + m)

main :: IO ()
main = start $
       do f <- frame [ text := "Alarm Specialized Example" ]
          p <- panel f []
          en <- genericWidget p (Alarm "My alarm" $ Minutes 117)
          b >= print ]
          set f [ layout := container p $ row 10 [ fill $ widget en, widget b ]
                , size := Size 550 165 ]

The italicized code show the interesting lines. These lines specifies how to present the Minutes type to the user. It is done by making Minutes an instance of WxGen. We use two WxGeneric functions to help us – toOuter and valuedCompose. valuedCompose uses the helper function, which must return a 5-tuple consisting of:

  1. Layout
  2. a get value action
  3. a set value action
  4. a get change listener action
  5. a set change listener action

the rest of the code should be familiar.

And the resulting GUI:

Alarm Specialized Example

The code has blown up in size, and you may think that this do not free you from a lot of work as compared to making the GUI directly in WxHaskell. However, we can reuse the specialization of the Alarm type in other data types. For example if we have big data type Foo, which includes the Alarm type, we just need to make sure that the Alarm WxGen-instance is in scope and it is automatically used when turning Foo into a widget.

Also the specialization can be made more general. We can make a WxGen instance for all lists. Indeed, the list instance is already included in the distribution of WxGeneric.

Modeling Alarm using a data type

Specializing the Alarm type as done in the last section may seem a little troublesome. And indeed there is another way:

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses
  , TemplateHaskell, UndecidableInstances #-}

module AlarmMapValue where

import Graphics.UI.WxGeneric
import Graphics.UI.SybWidget.MySYB

import Graphics.UI.WX
import Graphics.UI.WXCore

data Minutes = Minutes Int deriving (Show, Eq)
data Alarm = Alarm { name :: String
                   , timeOfDay :: Minutes
                   } deriving (Show, Eq)
data UserTime = UserTime { hour   :: Int
                         , minute :: Int
                         } deriving (Show, Eq)

$(derive [''Minutes,''UserTime,''Alarm])

instance WxGen UserTime
instance WxGen Alarm

instance WxGen Minutes where
    mkWid m' =
        let minutes2UserTime (Minutes m)    = UserTime (m `div` 60) (m `mod` 60)
            userTime2Minutes (UserTime h m) = Minutes (60*h + m)
        in mapValue userTime2Minutes (const minutes2UserTime) (mkWid (minutes2UserTime m'))

main :: IO ()
main = start $
       do f <- frame [ text := "Alarm Map Value" ]
          p <- panel f []
          en <- genericWidget p (Alarm "My alarm" $ Minutes 117)
          b >= print ]
          set f [ layout := container p $ row 10 [ widget en, widget b ]
                , size := Size 275 165 ]

In stead of modeling the interface using WxHaskell, toOuter and valuedCompose, we model it by another data type (UserTime). In the Minutes instance of WxGen we then describe how to translate between UserTime and Minutes.

And the resulting GUI:

Alarm Specialized by mapValue

Your Turn

Now it is your turn to play around with WxGeneric and maybe integrate WxGeneric into some of your WxHaskell projects. You will properly find that WxGeneric’s on-line available Haddock docs are useful. I would love to get feedback about your experiences.

2 Responses to “Using WxGeneric”

  1. Paczesiowa Says:

    images don’t work

  2. supermule Says:

    Hi Paczesiowa,

    The images should be visible now.

    Greetings,

    Mads


Leave a comment