AutoForms/Tutorial

From HaskellWiki
Jump to navigation Jump to search

A fair warning. This interface is experimental. And while it works for some examples, it do have it shortcomings.

Introduction

AutoForms is a library to ease the creation of Graphical User Interfaces (GUI). It so this by using generic programming to construct GUI components. The AutoForms user creates an ordinary algebraic data type (ADT), that reflects the data model of an application. From this ADT AutoForms automatically derives a GUI component, by using the structure and identifiers of the ADT

In this article we will see how AutoForms is used via a practical example. We will explain how AutoForms is used (the interface), rather than how it is implemented. And you should be able to see some of the advantages and disadvantages of the AutoForms library. In comparison to conventional GUI libraries, we aim to show that AutoForms can:

  • speed up the creation of GUI applications
  • abstract over a larger set of standard dialogs - by standard dialog we mean dialogs like a file dialog or an error dialog
  • more easily adapts to chageing requirements
  • stronger type safety

Furthermore, we aim to show that:

  • while AutoForms is build upon the automatic construction of GUI applications, using an ADT as input, we will show that it is still possible to customize the applications look and functionality

To understand this article the reader should have programming experience with Haskell and atleast have looked at the AutoForms homepage.

We will achieve the goals by creating a GUI frontend for a Cron-like daemon. We will start with a simple example and evolve more complex examples. This is not just to avoid presenting too many details at once, but also because it resembles a typical software development effort. The application is chosen as it is simple, yet practically usefull. Also, different aspects of the AutoForms library is presented well with this kind of application.

The reader is encouraged to download and run the examples. As the AutoForms library is build upon the cross platform library WxHaskell it should work on MS Windows, Apple, and Linux. The examples shown in this tutorial are included with the AutoForms library as well. If you install this library then you will be able to compile the HCron GUIs, shown in this article, by doing "cd src/Examples/HCron/ && make <editor name>". Or you can compile all of them by "cd src/Examples/HCron && make all".

The Cron Editors

Cron

Cron is a scheduling service for recurring jobs. It is normally only seen in Unix-(like) environments. Which jobs to run are decided by editing crontab-files using a text editor. For example the following crontab entry says that the job getMail should be every day 20 minutes past 10 o'clock.

20      10      *       *       *       getMail

This kind of service can be very useful. However, editing text files is not the easiest or most intuitive way to interface with a Cron-like service. A GUI should be able to do a much better job. Thus we want to create a GUI for a Cron-like service.

We have decided to make our own Cron-like daemon, in stead of using the standard Unix Cron, as:

  • our own tool can be cross platform.
  • parsing will be alot simpler, as we can store the Crontab-like file as an ordinary Haskell ADT. This will mean that we can use Haskell' show and read functions for serialization and deserialization.
  • we can have features not found in Cron, such as handling one-off jobs and not just recurring jobs.

Our first program

The daemon (service)

Before creating the GUI, we will create the daemon to execute the batch jobs. We have decided to begin by creating a very simple daemon, that can only execute jobs at a specified time. It cannot handle recurring jobs. We will laiter add more functionality to the daemon. Note that this resembles how much software is actually build, by starting with a simple prototype and then incrementally adding more functionality.

We will not go into detail about how the daemon is implemented, as it is not the point of this tutorial. However, the interested reader can look at the source code.

What is interesting is the data type the daemon uses to store which jobs to execute. This is important as the GUI needs to manipulate this datatype. The type is defined in the Entry1st module as:

type HCron = [Entry Time]

data Entry t = Entry { when    :: t
                     , command :: String } deriving (Show, Read, Eq, Ord)

data Time = Time { year   :: Int
                 , month  :: System.Time.Month
                 , day    :: Int
                 , hour   :: Int
                 , minute :: Int } deriving (Show, Read, Eq, Ord)

The module also defines:

specLocation = "./hcron.spec"

which is the file, where we will store our crontab entries.

The GUI

Now that we have made the daemon and the HCron data type, we are ready for what AutoForms is all about - user interfaces. We want to create a GUI to edit the HCron data type and to store the result.

We will show the code for our first GUI in small steps and explain each part as it is shown. Firstly,

module Editor1st where

import Entry1st
import Graphics.UI.AF.WxFormAll

we need to import the data type defined above (Entry1st) and to import WxFormAll, which makes it possible to use the AutoForms library.

To automatically generate GUIs, AutoForms uses the Scrap Your Boilerplate 3 (SYB3) approch to generic programming. SYB3 requires that we use the template-function derive for all data types we want to process generically. Thus we use derive on the Entry data type and its children:

$(derive [''Entry,''Time,''Month])

Finally we get to the main function, which constructs the GUI:

main = do entry <- (readFile specLocation >>= readIO) `catch` (\_ -> return [])
          let editorComponent :: EC HCron (Changed HCron)
              editorComponent = addButtons [save, quit] $ comState hasChangedState (mkCom entry)
          runAF $ window [] editorComponent
    where
      quit, save :: WxAction (Changed HCron) HCron
      quit = alwaysEnabled "Quit" closeWindow
      save = Action "Save" (\_ s -> hasChanged s) $
                 do x <- getVal
                    setState $ Unchanged x
                    liftIO $ writeFile specLocation (show x)

the first line reads the specification of jobs to execute and when from the file system. The file path is in the specLocation constant, which is defined in the Entry1st module. If this file cannot be read, it falls back to an empty specification, one with no jobs defined.

The second and third line specifies how our editor component (EC) is constructed. An EC is used to display and edit values. An EC do not just contains the widgets to edit values, but can also contain state and buttons (actions) to act upon those values. Therefore an EC has two type parameters: the edited value and the state.

Reading the third line from right to left, we first use mkCom to create an EC for HCron. It has the type EC HCron () , i.e. it has no state. But as the save button, we create below, should only be enabled when the edited value has changed, we use the comState function to attach state to our EC. We attach hasChangedState, which is a standard AutoForms state . Finally, we are ready to attach the two buttons: save and quit.

The fourth line starts the actual GUI. We use the window function to put the EC into a GUI window. Finally we run the GUI by calling runAF.

Lastly, we see the code for the two actions (the buttons). The quit-action is always enabled and will close the application when activated. The save actions is more complicated. It is only activated when the edited value has changed. When activated it reset the state to "Unchanged" and writes the contents of the specification to the file system.

As would be expected from a Haskell program, but not from conventional GUI toolkits, this GUI is constructed in a type-safe fashion.

Here you can find the complete code for the application. If you installed AutoForms you can compile the our GUI by doing "make Examples/HCron/Editor1st" from within the AutoForms source distribution.

Using standard dialogs

In the last section we saw that you could easily create a GUI with AutoForms. However, editing some file using a nice GUI seems like a common task. Thus we should be able to reuse as much of the functionality as possible, i.e. we should not have to create save & quit buttons every time we need to edit some file. And with the editFile function we can avoid this:

module Editor2nd where

import Entry1st
import Graphics.UI.AF.WxFormAll

$(derive [''Entry,''Time,''Month])

main = runAF $ editFile specLocation ([]::HCron)

that is all. Five lines of code and you have a GUI. This would not have been possible with a conventional GUI toolkit, as you need to specify the GUI elements and layout manually.

Again you can compile the application yourself, by doing "make Examples/HCron/Editor2nd" from within the AutoForms source code.

Editor with limits

The current editor accepts a lot more values than makes sense. For instance you can specify that you want the zero'th day of the month. It should not be a big surprise, as Haskell only lets us specify type constrains when they can be statically checked. This is not good enough for a user friendly GUI. We will therefore limit the possible values the GUI can have:

instance TypePresentation (Entry Time) tp1 tp2 tp3 where
   mkCom x = limit timeLimit ("Incorrect time")
                  (defaultCom x)
       where
         timeLimit :: Entry Time -> IO Bool
         timeLimit Entry { when = Time y month d h m } = return $
           y > 1970   && y < 2100    &&
           d >= 1                    &&
           ((month == February && d <= 28)                   ||
            (month == February && d == 29 && y `mod` 4 == 0) ||
            (month `elem` [ January, March, May, July, August
                          , October, December] && d <= 30)   ||
            (month `elem` [April, June, September, November] && d <= 30)
           )                         &&
           h >= 0     && h <= 23     &&
           m >= 0     && m <= 59

we do this by specializing the Entry Time (remember Entry has one type parameter) type for TypePresentataion. Reading the mkCom function backwards, we first call defaultCom which constructs a default GUI for Entry Time. We then limit this default GUI to accept only sensible values using the timeLimit function. The GUI will complain with "Incorrect time" if the user inputs a non-sensible value.

Not only is this specification succint, it also manages to separate the set of legal values from laying out GUI elements and from the interactive aspects of the GUI. In conventional GUI toolkits this restriction of legal values are intermixed with the GUI element creation and/or layout of elements.

Finally, we need to add a default Time value by specializing GInstanceCreator:

instance GInstanceCreator Time where
    gGenUpTo _ = [Time 2000 January 1 10 00]

Again you can compile the application yourself, by doing "make Examples/HCron/Editor3rdLimit" and you can find the source code here.

Recurring tasks

We set out to create a crontab-like GUI editor. But crontab handles recurring tasks and we do not. First we add recurring tasks to the Entry data type by adding a recurring field and changing the daemon accordingly:

data Entry t = Entry { when      :: t
                     , recurring :: Maybe TimeDiff
                     , command   :: String } deriving (Show, Read, Eq, Ord)

We also need to change the GUI. This is done by adding TimeDiff to the derive template function:

$(derive [''Entry,''Time,''Month,''TimeDiff])

that is, we need to tell AutoForms to construct GUI elements for the TimeDiff datatype. With conventional toolkits we would have to specify a new layout of elements, but with AutoForms it is done automatically. The changing requirements leeves us with almost no extra work for the GUI part.

The new GUI can be compiled by doing "make Examples/HCron/Editor4thRecurring.hs" and you can find the source code here.

Executing commands

As pointy-haired booses are known for, we are presented with yet another change in requirements. The GUI should now be able to execute the commands directly. To facilitate this change, TypePresentation is specialicalized to:

instance (Sat (tp2 (Entry Time, [String])), Sat (tp2 [String]), MonadIO m)
   => TypePresentation (Entry Time) tp1 tp2 m where
   mkCom x = limit timeLimit ("Incorrect time") $
                label "Entry" $
                fstCom $
                addButtons [execAction] $
                join (defaultCom x) (label "Command output" $ display [""])
                  -- defaultCom (x, ["Output area:", ""]) -- results in never-ending loop
       where
         execAction = alwaysEnabled "Exec..." $
                         do (entry, _)  <- getVal
                            (_, out) <- liftIO $ readCommand (Entry.command entry) ""
                            setVal (entry, lines out)
                            return ()
         timeLimit :: Entry Time -> IO Bool
         ...

again explaining mkCom backwards, we join a list of strings component with the default Entry component, thus creating the output area for the command execution. We then add the execute action. However, we do not want a type of (Entry Time, [String]) - we just want Entry Time. Thus we use the fstCom function. We finally label the type "Entry" and apply the timeLimit function.

The alterType function is important as it allows us to change the presentation of our Entry Time editor component (adding the output area), without changing the model (value) of our editor component.

The readCommand function is defined in the Run module and executes a command yielding a return code and the output.

The new GUI can be compiled by doing "make Examples/HCron/Editor5thOutputWindow.hs" and you can find the source code here.

Making a GUI for Cron

Most people using Unix-like operating systems, would probably prefer to keep using the ordinary Crontab daemon. Some may even suggest that just creating a new daemon (made to fit the AutoForms library) is a cop-out. To satiesfy these people and to make a more usefull application we have created a GUI for Crontab.

How this GUI works is left as an exercise for the reader.

Future work

While the GUIs above did show that AutoForms has potential, the GUIs were still small and the development of AutoForms has been directed by the needs of this tutorial. Therefore we need to create larger and more complex applications. We need this both to verify that AutoForms can be used for larger applications and to direct the development of AutoForms. To begin this work, we are currently creating a GUI for GHCi.

Also the layout of GUI elements is not nearly as nice as it could be. This needs to be improved for AutoForms to become a serious alternative as a GUI toolkit.

Acknowledgements

I would like to thank Kido Takahiro as an early adaptor of AutoForms, with his Kamiariduki project. I would also like to thank him for valuable feedback.

Also the creatators of Scrap Your Boilerplate should be mentioned, without whom this project would not be possible.

Finally, the creators of the GEC toolkit should be mentioned as many ideas was borrowed from them.