Building a text editor (Part 5)

In this section of the tutorial, we add find/replace functionality to the editor. Much of the required support is built-in to the textCtrl, but it is only exposed by the wxCore library, so we have a rather thin wrapper over the wxWidgets C++ code to work with.

Once more, we need to work around a couple of bugs in wxHaskell – the find/replace identifiers are defined incorrectly (or missing), so we hide the imported versions and replace them later on with the correct values. We also require a couple of extra pieces of library code.

> import Graphics.UI.WXCore hiding (wxID_CUT, wxID_COPY, wxID_PASTE,
>                                   wxID_FIND, wxID_FORWARD, wxID_BACKWARD)
> import Data.Bits
> import Data.Char (toLower)
> import Data.List

We maintain a copy of the user-selected find/replace options. The user can select: the search direction; whether the operations are case sensitive; whether to look for whole word matches only and whether to wrap around from the end of the document back to the start. We wrap all of this information in a data structure.

We also need to add an extra field to our GUICtx context state. This holds a FindReplaceData (), which is an object used by many of the functions associated with the textCtrl find/replace functionality exposed in wxCore. The internal details of FindReplaceData are opaque to the Haskell wrapper, but basically it is an object which maintains state on behalf of the find/replace dialog box.

> data FRFlags = FRFlags { frfGoingDown :: Bool,
>                          frfMatchCase :: Bool,
>                          frfWholeWord :: Bool,
>                          frfWrapSearch :: Bool
>                        }
>                deriving (Eq, Show)
> data GUIContext = GUICtx { guiWin    :: Frame (),
>                            guiEditor :: TextCtrl (),
>                            guiFile   :: Var (Maybe FilePath),
>                            guiTimer  :: TimerEx (),
>                            guiPast   :: Var [String],
>                            guiFuture :: Var [String],
>                            guiSearch :: FindReplaceData ()
>                          }

As mentioned earlier, some of the identifiers in Graphics.UI.WXCore.WxcDefs are incorrect:

> wxID_FIND, wxID_FORWARD, wxID_BACKWARD, wxID_REPLACE :: Id
> wxID_FIND       = 5035
> wxID_REPLACE    = 5038  -- This one is not in WxcDefs, so not hidden earlier
> wxID_FORWARD    = 5106
> wxID_BACKWARD   = 5107

Changes to the GUI function

As usual, a few changes are needed to the top-level GUI function (step5 in this case).

To make use of the find/replace dialog box, we create a FindReplaceData instance. This will be maintained in the GUI context state structure. In this case it is created with a default indicating that forward search (wxFR_DOWN) is selected. You could also use any of the following:

  • wxFR_WHOLEWORD to indicate that search/replace should only take place on whole words.
  • wxFR_MATCHCASE to indicate that case sensitive search/replace is selected.

As well as configuring when the FindReplaceData instance is created, you can use findReplaceDataSetFlags to do the same thing. If you choose to do this, please note that according to the wxWidgets documentation, these flags can only be changed before the find/replace dialog box is first shown. Once the dialog has been shown, the values selected in the dialog are used, and changes have no effect.

> future <- varCreate []
> search <- findReplaceDataCreate wxFR_DOWN
> let guiCtx = GUICtx win editor filePath refreshTimer past future search
> set editor [on keyboard := \_ -> restartTimer guiCtx >> propagateEvent]

We also need to add menu entries and menu event handlers. Since these have been covered extensively before, no need for further comment:

> menuAppend mnuEdit wxID_PASTE "&Paste\tCtrl-v" "Paste" False
> menuAppendSeparator mnuEdit
> menuAppend mnuEdit wxID_FIND "&Find...\tCtrl-f" "Find" False
> menuAppend mnuEdit wxID_FORWARD "Find &Next\tCtrl-g" "Find Next" False
> menuAppend mnuEdit wxID_BACKWARD "Find &Previous\tCtrl-Shift-g" "Find Previous" False
> menuAppend mnuEdit wxID_REPLACE "&Replace...\tCtrl-Shift-r" "Replace" False
> evtHandlerOnMenuCommand win wxID_PASTE $ paste guiCtx
> evtHandlerOnMenuCommand win wxID_FIND $ justFind guiCtx
> evtHandlerOnMenuCommand win wxID_FORWARD $ justFindNext guiCtx
> evtHandlerOnMenuCommand win wxID_BACKWARD $ justFindPrev guiCtx
> evtHandlerOnMenuCommand win wxID_REPLACE $ findReplace guiCtx
> set win [menuBar := [mnuFile, mnuEdit]]

Dialog box functions

The dialog boxes used for both search and replace are launched by the same function – it is simply the dialog box style which changes, along with the text at the top of the dialog box. We use a couple of helper functions to make this explicit, and to keep our menu event handler functions simple:

To open a ‘find’ dialog box:

> justFind guiCtx = openFindDialog guiCtx "Find..." dialogDefaultStyle

To open a ‘replace’ dialog box, we need to modify the dialog box style to indicate that a ‘replace’ dialog box is wanted. In wxWidgets, control styles are usually represented by integers, with various stylistic elements represented by setting (or not) particular bits in the style integer.

For the built-in standard dialog boxes, there is a value dialogDefaultStyle which represents the default stylistic attributes of the control. It can be updated by setting or clearing specific flags, which we do using functions from Data.Bits. I’m probably not teaching anyone anything new here (it’s binary operations 101), but just in case…

  • To set a bit denoted by ‘flag’, use the logical ‘OR’ function (this is (.|.) in Haskell), e.g value’ = value .|. flag
  • To clear a bit denoted by ‘flag’, use the logical ‘NOT’ and logical ‘AND’ functions (complement and (.&.) in Haskell), e.g. value’ = value .&. (complement flag)
> findReplace guiCtx = openFindDialog guiCtx "Find and Replace..."
>                    $  dialogDefaultStyle .|. wxFR_REPLACEDIALOG

Let’s look at the code to handle the dialog box itself. I’ll cover this in some detail, as many of the built-in wxHaskell dialogs require similar handling.

The first line is straightforward: create the find/replace dialog instance. It is not visible by default, so we can continue to configure it without things looking strange for the user. There are a few things to notice:

  • The dialog box is associated with a parent window – in this case the Frame inside which the editor instance sits.
  • The dialog box requires an instance of FindReplaceData – we use the one we created in the top level of the GUI, and saved in the GUI context state variable.
  • The dialog style we set in either findReplace or justFind is being modified further, disabling whole word search.

The next lines are more complex. The purpose is to set event handlers for each of the events which can be handled by the find/replace dialog.

There are a few things we need to get correct for this to work. The first problem is to ensure that the GUI context is passed to the event handlers as required (it is a curried parameter they expect to receive). The second is to ensure that the events are propagated to other windows even if they are processed by the find/replace dialog event handlers.

Let’s take a look at the windowOnEvent function. This is one area where a quick look at the wxWidgets documentation will not help you much. This is because event handling in wxWidgets is hidden under an opaque macro layer which hides much of the complexity from the C++ programmer, but doesn’t help the user of a language binding like wxHaskell very much.

The signature of windowOnEvent is:

windowOnEvent :: Window a -> [EventID] -> handler -> (Event () -> IO ()) -> IO ()
windowOnEvent window events state eventHandler

The parameters are:

  • window The window to this the event handler is attached – in this case our dialog box.
  • events A list of the event IDs to which the event handler will respond. A list is required here because the event handler may respond to multiple events.
  • state Any Haskell data the programmer wishes to associate with the event handler. This is often set to be the main event handler function, since it allows the event handler to be straightforwardly retrieved (there is a function unsafeGetHandlerState to do this if required).
  • eventHandler The user-provided function to handle the event.This must be of type Event () -> IO ().

Let’s step through what happens when calling windowOnEvent:

  1. windowOnEvent window events state eventHandler is a pseudonym for  windowOnEventEx window events state (\ownerDelete -> return ()) eventHandler. In other words, we are creating an event handler where we take on the responsibility for any clean-up required when the event handler is deleted. This is the most usual case (the garbage collector normally takes care of the rest), but it you need it, there is always windowOnEventEx where you provide your own clean-up function.
  2. Disconnect any existing event handlers, calling eventHandlerOnEventDisconnect. Please note (if you are planning on  using any multi-threading) that this call modifies non thread-safe global state.
  3. Create a closure containing state, a clean-up function and a function which is called when an event occurs.
  4. For each event in events, call evtHandlerConnect (a wrapper around the wxWidgets function wxEvtHandler::Connect()). The closure created in the previous step is passed as user data.

What all of this means in practice is that a call to windowOnEvent associates an event handler and a piece of user-provided data with a particular eventID on a given window.

Let’s look at the implementation, working back from usage:

  • A call to winSet wxEVT_COMMAND_FIND findNextButton associates the event wxEVT_COMMAND_FIND with the event handler findNextButton.
  • This is equivalent to let hnd _ = findNextButton guiCtx >> propagateEvent in windowOnEvent frdialog [wxEVT_COMMAND_FIND] hnd hnd
  • Which is equivalent to windowOnEvent frdialog [wxEVT_COMMAND_FIND] (findNextButton guiCtx >> propagateEvent) (findNextButton guiCtx >> propagateEvent)

Incidentally, another, possibly slightly clearer (and more verbose) way of writing effectively the same code is:

  • windowOnEvent [wxEVT_COMMAND_FIND] findNextHdlr (\evt -> findNextHdlr)
    where findNextHdlr = findNextButton guiCtx >> propagateEvent

Finally, set the dialog box to be visible, and we’re done.

> openFindDialog :: GUIContext -> String -> Int -> IO ()
> openFindDialog guiCtx@GUICtx{guiWin = win, guiSearch = search} title dlgStyle =
>  do
>    frdialog <- findReplaceDialogCreate win search title
>                         $ dlgStyle .|. wxFR_NOWHOLEWORD
>    let winSet k f = let hnd _ = f guiCtx >> propagateEvent
>    in  windowOnEvent frdialog [k] hnd hnd
>    winSet wxEVT_COMMAND_FIND findNextButton
>    winSet  wxEVT_COMMAND_FIND_NEXT findNextButton
>    winSet  wxEVT_COMMAND_FIND_REPLACE findReplaceButton
>    winSet  wxEVT_COMMAND_FIND_REPLACE_ALL findReplaceAllButton
>    set frdialog [visible := True]

Find next / previous

The functions to find the next and previous matches are very similar, and each is a wrapper around the findNextButton function.

In the case of justFindNext we retrieve the FindReplaceData and force the search direction to be downwards. For justFindPrev we set the search direction upwards.

> justFindNext guiCtx@GUICtx{guiSearch = search} =
>  do
>    curFlags <- findReplaceDataGetFlags search
>    findReplaceDataSetFlags search $ curFlags .|. wxFR_DOWN
>    findNextButton guiCtx
> justFindPrev guiCtx@GUICtx{guiSearch = search} =
>  do
>    curFlags <- findReplaceDataGetFlags search
>    findReplaceDataSetFlags search
>                        $ curFlags .&. complement wxFR_DOWN
>    findNextButton guiCtx

To make it easier to work with the flags in a FindReplaceData, we have an auxiliary data structure FRFlags (which was defined earlier) and a function buildFRFlags to construct the data structure from the flags in a FindReplaceData. Note also that there is an additional parameter in FRFlags which is not present in FindReplaceData. This indicates whether we should wrap our searches around the text buffer, and is set by a Bool parameter to buildFRFlags.

> buildFRFlags :: Bool  -> Int  -> IO FRFlags
> buildFRFlags w x =
>   return FRFlags {frfGoingDown = (x .&. wxFR_DOWN) /= 0,
>                   frfMatchCase = (x .&. wxFR_MATCHCASE) /= 0,
>                   frfWholeWord = (x .&. wxFR_WHOLEWORD) /= 0,
>                   frfWrapSearch = w}

The findNextButton function is responsible for finding the next occurrence of the search text, taking into account all of the user preferences. It is worth noting that this function can be called both when the find/replace dialog is opened, as a result of menu selections, or as a result of hot-key combinations being pressed. This works because we retain the FindReplaceData from the last time the find/replace menu was open at all times, and pass it around as a curried parameter.

This function is pretty much a template for most of the remaining find/replace functions.

We first get the search string and flags from the FindReplaceData. The findReplaceDataGetFindString function returns the search string (s) and findReplaceDataGetFlags returns the search/replace flags. The flags are piped into buildFRFlags to obtain the flags (fs). Note that in this case we are forcing the case that the user wishes to wrap the search around the text buffer.

The findMatch function returns the location (insertion point) at which the match was found. Since it is possible that there is no match, this is wrapped up in a Maybe.

If we successfully find a match, we set the insertion point to the start of the match, then select the matched text (we can do this because we know the length of the text matched). If no match is found, we pop up a dialog box – you might prefer to do nothing in this case!

> findNextButton guiCtx@GUICtx{guiEditor = editor, guiWin = win,
>                              guiSearch= search} =
>  do
>    s  <- findReplaceDataGetFindString search
>    fs <- findReplaceDataGetFlags search >>= buildFRFlags True
>    mip <- findMatch s fs editor
>    case mip of
>        Nothing -> infoDialog win "Find Results" $ s ++ " not found."
>        Just ip -> do
>                     textCtrlSetInsertionPoint editor ip
>                     textCtrlSetSelection editor ip (length s + ip)

The findReplaceButton function is similar in many respects to findNextButton, but now we need to worry about updating the GUI history.

> findReplaceButton guiCtx@GUICtx{guiEditor = editor, guiWin = win,
>                                 guiSearch = search} =
>  do
>    s <- findReplaceDataGetFindString search
>    r <- findReplaceDataGetReplaceString search
>    fs <- findReplaceDataGetFlags search >>= buildFRFlags True
>    mip <- findMatch s fs editor
>    case mip of
>        Nothing -> infoDialog win "Find Results" $ s ++ " not found."
>        Just ip -> do
>                     textCtrlReplace editor ip (length s + ip) r
>                     textCtrlSetInsertionPoint editor ip
>                     textCtrlSetSelection editor ip (length r + ip)
>                     updatePast guiCtx

The findReplaceAllButton function is a further development of findReplaceButton. One of the key changes is that we no longer wrap our searches, as this carries a risk of infinite loops. Instead, we explicitly set the insert point (using textCtrlSetInsertionPoint) to the start of the text before doing the replacement. This is essentially equivalent to performing a wrapped replace all.

The main work of replacing all instances falls to the auxiliary function replaceAllIn. This is the same piece of code as used to do text replacement in findReplaceButton except that it is called recursively until there are no further matches

> findReplaceAllButton guiCtx@GUICtx{guiEditor = editor,
>                                    guiSearch = search} =
>  do
>    s <- findReplaceDataGetFindString search
>    r <- findReplaceDataGetReplaceString search
>    fs <- findReplaceDataGetFlags search >>= buildFRFlags False
>    textCtrlSetInsertionPoint editor 0
>    replaceAllIn s r fs editor
>    updatePast guiCtx
>      where
>        replaceAllIn s r fs editor =
>         do
>           mip <- findMatch s fs editor
>           case mip of
>               Nothing -> return () -- we're done here
>               Just ip -> do
>                            textCtrlReplace editor ip (length s + ip) r
>                            textCtrlSetInsertionPoint editor $ length r + ip
>                            replaceAllIn s r fs editor

Matching text in a TextCtrl

The findMatch function looks for text which matches the search criteria, and returns the position of the first match or Nothing.

A TextCtrl models its contents as a string, and represents the insertion point as zero-indexed offset from the start of the string. It is worth noting that some criticism could be made of the memory usage of the implementation below – this would be valid for extremely large files (we are taking a copy of the text control contents when we call textCtrlGetInsertionPoint), but the wxWidgets text control is really only useful for relatively small files – up to around 64kB (this is a hard limit on some platforms). If you are interested in working on very large files, you will probably want to implement a custom control. In any case, the approach shown is quite reasonable for demonstration purposes, and for any reasonable use of TextCtrl!

If we are doing case-insensitive search, the simplest thing to do is to transform the search and replace strings to lower case. Note that this does not affect the text in the control (we are working on a copy) or the actual text we use to replace matches (we are also working with a copy!).

We use separate functions for searching forwards (nextMatch) and backwards (prevMatch). These each return both the position of the match in the string (which is the same as the insertion point in the text control) and an indication of whether they needed to wrap around to get a match (this will disallow a match if wrap was disabled).

> findMatch query flags editor =
>  do
>   txt <- get editor text
>   ip <- textCtrlGetInsertionPoint editor
>   let (substring, string) = if frfMatchCase flags
>                             then (query, txt)
>                             else (map toLower query, map toLower txt)
>   funct = if frfGoingDown flags
>           then nextMatch (ip + 1)
>           else prevMatch ip
>   (mip, wrapped) = funct substring string
>   return $ if (not $ frfWrapSearch flags) && wrapped
>            then Nothing
>            else mip

The prevMatch and nextMatch functions are pretty similar.

The base case for prevMatch is that you are looking for an empty string. The most logical thing to do when looking for nothing is to find nothing, so:

> prevMatch _ [] _ = (Nothing, True)

The first condition in prevMatch for other cases is a check that we have not wrapped around from start of string. If we have (or would during the search) then we restart the search from then end of the string.

Otherwise, we use the nextMatch function to find our matches. To use nextMatch when we are supposed to be going backwards requires us to reverse both the substring and the string being searched, as well as changing the insert point to reflect position from the end of the string, rather than the start.

> prevMatch from substring string
>     | length string < from || from <= 0 =
>           prevMatch (length string) substring string
>     | otherwise =
>     case nextMatch (fromBack from)
>                    (reverse substring) (reverse string) of
>         (Nothing, wrapped) ->
>             (Nothing, wrapped)
>         (Just ri, wrapped) ->
>             (Just $ fromBack (ri + length substring), wrapped)
>       where
>         fromBack x = length string - x

The base case for nextMatch is exactly the same as for prevMatch, and for the same reasons.

> nextMatch _ [] _ = (Nothing, True)

The first condition covers the case where the substring is longer than the string. No search can every succeed in this case, and the search would wrap.

The second condition covers the case where searching would cause wrap-around, and we restart from the beginning of the string.

The third (normal) case works as follows:

  • Drop the characters before the (current) insertion point. If we find a match here, then we successfully matched without wrapping around the text.
  • Take all of the characters before the insertion point and further characters up to the length of the substring. If we find a match hers, then we successfully matched, but needed to wrap around to do so.
> nextMatch from substring string
>     | length substring > length string = (Nothing, True)
>     | length string <= from = nextMatch 0 substring string
>     | otherwise =
>   let after = drop from string
>       before = take (from + length substring) string
>       aIndex = indexOf substring after
>       bIndex = indexOf substring before
>   in case aIndex of
>          Just ai -> (Just $ from + ai,  False)
>          Nothing -> case bIndex of
>                         Nothing -> (Nothing, True)
>                         Just bi -> (Just bi, True)

The indexOf function finds the location of a given substring in a string.

> indexOf substring string = findIndex (isPrefixOf substring) $ tails string

Building a text editor (Part 4)

In this very short post we add copy/cut/paste support to the editor. These will be accessible from the menu as well as by using the usual CUA keystrokes (Ctrl-C, Ctrl-X, Ctrl-V).

Most of the required functionality is provided by the TextCtrl itself, so the code mainly consists of connecting up event handlers to bind to the TextCtrl functions.

The first issue we need to deal with is a wxHaskell bug – this will be fixed shortly, but in the meantime it is worth knowing about. The problem is that wxHaskellprovides the wrong constants for wxID_CUT, wxID_COPY and wxID_PASTE, which are the standard identifiers used by the text control.

As always, changed text id highlighted in red.

 > import Graphics.UI.WXCore hiding (wxID_CUT, wxID_COPY, wxID_PASTE)

We can now put the correct values in ourselves. These are ‘magic’ numbers, and you’ll have to trust me that they are correct – it is not particularly easy to work out the correct values without wading through lots of C++ code.

 > wxID_MYUNDO, wxID_MYREDO, wxID_CUT, wxID_COPY, wxID_PASTE :: Id
 > wxID_MYUNDO = 5107
 > wxID_MYREDO = 5108
 > wxID_CUT    = 5031
 > wxID_COPY   = 5032
 > wxID_PASTE  = 5033

We now add the menu items and their event handlers. Nothing new here: we’ve looked at menus before. These go into the GUI top level function, along with the other UI component definitions.

 > menuAppendSeparator mnuEdit
 > menuAppend mnuEdit wxID_CUT "C&ut\tCtrl-x" "Cut" False
 > menuAppend mnuEdit wxID_COPY "&Copy\tCtrl-c" "Copy" False
 > menuAppend mnuEdit wxID_PASTE "&Paste\tCtrl-v" "Paste" False

 > evtHandlerOnMenuCommand win wxID_CUT $ cut guiCtx
 > evtHandlerOnMenuCommand win wxID_COPY $ copy guiCtx
 > evtHandlerOnMenuCommand win wxID_PASTE $ paste guiCtx

We also require three new event handler functions:

— We just copy the selected text

The copy function simply uses the textCtrlCopy function provided by the control. Remember (see part 2) that we use GUICtx as a way to pass around the global state (the GUI widgets).

 > copy GUICtx{guiEditor = editor} =
 >   textCtrlCopy editor

The cut function also uses the standard editor functionality, but in this case we are modifying the contents of the TextCtrl and we must update the GUI with an undo action.

 > cut guiCtx@GUICtx{guiEditor = editor} =
 >   textCtrlCut editor >> updatePast guiCtx

The paste function also modifies the undo history.

 > paste guiCtx@GUICtx{guiEditor = editor} =
 >   textCtrlPaste editor >> updatePast guiCtx

Building a text editor (Part 3)

(Update: The original version of this installment included code which caused a memory leak. Fernando has fixed the code, and I recommend that you look at the latest version of wxhnotepad (cabal fetch wxhnotepad). I have updated the tutorial text below.)

This is the third installment of a series looking at wxhNotepad, a wxHaskell application written by Fernando Benavides, and this is where things start to become more interesting as we are adding some real functionality – in this case undo and redo functionality.

The wxHaskell TextCtrl () does, in fact, contain undo / redo support. It is not really ideal for a text editor, however, since it allows ‘undo’ on a new text file, for example.

GUI top level

The first thing to do is to extend the GUIContext type to maintain undo and redo history, each of which we express as a list of strings. There is also a TimerEx (), and this requires a little more explanation. The details will become clearer as we work through the code, but basically we use the timer as a means to help us to group ‘undoable’ and ‘redoable’ actions into larger units than characters.

As in the previous post, new code is highlighted in red.

> data GUIContext = GUICtx { guiWin    :: Frame (),
> guiEditor :: TextCtrl (),
> guiFile   :: Var (Maybe FilePath),
> guiTimer  :: TimerEx (),       -- ^ A timer to detect user actions
> guiPast   :: Var [String],     -- ^ For Undo history
> guiFuture :: Var [String]      -- ^ For Redo history
> }

Because we are not using the built-in undo/redo functionality in the TextCtrl, we need to define some unique menu identifiers. These must not conflict with identifiers in use elsewhere in the application. The numbers used are ‘magic’ – there is currently no convenient way to ensure that there is no such conflict – something which should probably be fixed in a future release of wxHaskell.

> wxID_MYUNDO, wxID_MYREDO :: Id
> wxID_MYUNDO = 5107
> wxID_MYREDO = 5108

Most of the changes to the top level GUI function require little comment as we have discussed the details in earlier installments.

> step3 :: IO ()
> step3 =
>   do
>     win <- frame [text := "wxhNotepad - Step 3", visible := False]
>     editor <- textCtrl win [font := fontFixed,
>                             text := "Undo / Redo support is ready by " ++
>                                     "default on text controls..."]
>     filePath <- varCreate Nothing

We create a timer instance in much the same way as any wxHaskell control. The timer interval is set to 1000 seconds (10^6ms).

The timer is used in an interesting way. Each time a keyboard event is received, restartTimer is called before sending the keyboard event on to the TextCtrl (we do this with the call to propagateEvent, which passes any interecpted event on to other controls which might wish to respond to it). In restartTimer a shorter (1 sec) timer interval is used to group input into chunks a little longer than a single character, so that undo and redo work on more meaningful chunks of text.

Once the timer has been created, we call updatePast to begin recording the undo/redo stream.

>     refreshTimer <- timer win []
>     past <- varCreate []
>     future <- varCreate []
>     let guiCtx = GUICtx win editor filePath refreshTimer past future
>     timerOnCommand refreshTimer $ updatePast guiCtx
>     set editor [on keyboard := \_ -> restartTimer guiCtx >> propagateEvent]
>     updatePast guiCtx

The remainder of the changes in the GUI top level relate to the extra menu entries to support undo and redo. These follow the pattern described in the previous post.

>     mnuFile <- menuPane [text := "File"]
>     mnuEdit <- menuPane [text := "Edit"]
>     menuAppend mnuFile wxID_OPEN "&Open...\tCtrl-o" "Open Page" False
>     menuAppend mnuFile wxID_SAVE "&Save\tCtrl-s" "Save Page" False
>     menuAppend mnuFile wxID_SAVEAS "Save &as...\tCtrl-Shift-s" "Save Page as" False
>     menuAppend mnuFile wxID_CLOSE "&Close\tCtrl-W" "Close Page" False
>     menuAppend mnuEdit wxID_MYUNDO "&Undo\tCtrl-z" "Undo last action" False
>     menuAppend mnuEdit wxID_MYREDO "&Redo\tCtrl-Shift-z" "Redo last undone action" False
>     evtHandlerOnMenuCommand win wxID_OPEN $ openPage guiCtx
>     evtHandlerOnMenuCommand win wxID_SAVE $ savePage guiCtx
>     evtHandlerOnMenuCommand win wxID_SAVEAS $ savePageAs guiCtx
>     evtHandlerOnMenuCommand win wxID_CLOSE $ windowClose win False >> return ()
>     evtHandlerOnMenuCommand win wxID_MYUNDO $ undo guiCtx
>     evtHandlerOnMenuCommand win wxID_MYREDO $ redo guiCtx
>     set win [menuBar := [mnuFile, mnuEdit]]
>     set win [layout := fill $ widget editor,
>              clientSize := sz 640 480]
>     focusOn editor
>     set win [visible := True]

File Handling Events

The changes to the file handling are very minimal – just a couple of lines in openPage so that the undo history is cleared when a new file is opened, and then populated with the initial file text (since this represents the first state of the ‘undo’ action list).

> openPage guiCtx@GUICtx{guiWin = win, guiEditor = editor, guiFile = filePath} =
>   do
>   maybePath <- fileOpenDialog win True True "Open file..."
>                               [("Haskells (*.hs)",["*.hs"]),
>                                ("Texts (*.txt)", ["*.txt"]),
>                                ("Any file (*.*)",["*.*"])]
>                               "" ""
>   case maybePath of
>     Nothing   -> return ()
>     Just path -> do
>                  clearPast guiCtx
>                  textCtrlLoadFile editor path
>                  updatePast guiCtx
>                  set win [text := "wxhnotepad - " ++ path]
>                  varSet filePath $ Just path

There is a new event handler for the ‘undo’ menu item.

> undo guiCtx@GUICtx{guiEditor = editor, guiPast = past, guiFuture = future} =
>   do
>     -- Now we try to detect if there's something new and kill the timer
>     updatePast guiCtx
>     history <- varGet past
>     case history of
>       []            -> return () -- Nothing to be undone
>       [t]           -> return () -- Just the initial state, nothing to be undone
>       tnow:tlast:ts -> do
>                          -- We add an action to be done on redo
>                          varUpdate future (tnow:)
>                          -- we remove it from the history
>                          varSet past $ tlast:ts
>                          -- and set the editor accordingly
>                          set editor [text := tlast]

The ‘redo’ menu item is handled similarly…

> redo guiCtx@GUICtx{guiEditor = editor, guiPast = past, guiFuture = future} =
>   do
>     -- First of all, we try to detect if there's something new
>     updatePast guiCtx
>     coming <- varGet future
>     case coming of
>       []   -> return () -- Nothing to be redone
>       t:ts -> do
>         -- remove it from the coming actions
>         varSet future ts
>         -- move it to the history actions
>         varUpdate past (t:)
>         -- and set the editor accordingly
>         set editor [text := t]

The updatePast function adds a new event to the undo history list. When updatePast is called, both the history and current editor text (tnow) are fetched and compared. If the head of the history list is not the same as the editor text, record the change.

> updatePast guiCtx@GUICtx{guiEditor = editor, guiPast = past, guiFuture = future} =
>  do
>    tnow    <- get editor text
>    history <- varGet past
>    case history of
>      []  -> varSet past [tnow]
>      t:_ -> if t /= tnow -- if there was a real change, we recorded it
>             then do
>               varUpdate past (tnow:)
>               varSet future [] -- we clean the future because the user is writing a new one
>             else     -- otherwise we ignore it
>               return ()
>               -- Now that history is up to date, we let the timer rest until new activity
>               -- is detected
>               killTimer guiCtx

The clearPast function clears the undo (past) and redo(future) lists.

> clearPast GUICtx{guiPast = past, guiFuture = future} =
>  do
>    varSet past []
>    varSet future []

The restartTimer function is used as part of a mechanism to try to separate undo/redo information into useful chunks instead of individual characters. This is done by starting a short duration (1 sec) timer which gets reset each time there is input from the user. The result is that we have a ‘timer’ which times out whenever the user pauses typing for more than a second. This is called from the textCtrl keyboard event handler, and allows us to group keyboard input according to natural pauses in typing.

> restartTimer guiCtx@GUICtx{guiWin = win, guiTimer = refreshTimer} =
>  do
>    started <- timerStart refreshTimer 1000 True
>    if started
>        then return ()
>        else do
>           errorDialog win "Error" "Can't start more timers"
>           wxcAppExit

The killTimer function starts a new timer of very long duration (something around 20 minutes). Should the timer expire, no action is taken, as the purpose here is simply to wait for some keyboard activity.

> killTimer GUICtx{guiTimer = refreshTimer} = timerStop refreshTimer

Note: there is a memory leak in this code

Building a text editor (Part 2)

In this installment, we will extend the text editor with some essential basic functionality: a menu bar and the ability to load and save files. Code which is new or changed from part 1 is highlighted in red (that’s most of the code in this case!)

The top level GUI function

Something which rapidly becomes an issue when coding real wxHaskell applications is the fact that there’s quite a bit of state which you find yourself passing around to many of the functions. In particular, you will often find that, say, and event handler for one control will want to perform some action(s) on other controls. You can, of course, pass all of this information around as curried function parameters, but it quickly gets out of hand.

The most common approach in wxHaskell applications is to create one or more types which hold the required state information and keep these in some suitable data structure. This way you only have one value to curry rather than several. GUIContext is the type we use in this application. It’s not really needed at this point in the evolution of our editor, but it will be useful later.

The Var type is conceptually rather similar to an MVar or an IORef. It’s a place to put mutable data, with the benefit that support is already built-in to wxHaskell. As with MVar and the like, it must be created (using varCreate) before it can be used.

  • guiWin contains the Frame which owns the controls in the text editor.
  • guiEditor is the textCtrl instance we use to display and edit text.
  • guiFile is a mutable variable used to hold the path to the file being edited. It is a Maybe type as a newly created file has no filename until it has been saved.
 > data GUIContext = GUICtx { guiWin    :: Frame (),
 >                            guiEditor :: TextCtrl (),
 >                            guiFile   :: Var (Maybe FilePath) > }
 >
 > step2 :: IO ()
 > step2 =
 >  do
 >  win <- frame [text := "wxhNotepad - Step 2", visible := False]
 >  editor <- textCtrl win [font := fontFixed,
 >                          text := "Now the user can open a file, save it" ++
 >                                  "or save it with another name.\n" ++
 >                                  "Our program is smart enough to remember" ++
 >                                  "the path of the last opened/saved file\n" ++
 >                                  "Note that we're *not* catching any " ++
 >                                  "filesystem errors here.  That's left " ++
 >                                  "as homework for you :P"]
 >  filePath <- varCreate Nothing
 >  let guiCtx = GUICtx win editor filePath

In the last installment, we saw how to use the declarative approach to creating a menu in Graphics.UI.WX.Menu. You can also use the lower-level functions in Graphics.UI.WXCore, and that is what we do here. If you follow the documentation link, you will see that the documentation is extremely minimal. Typically is just gives the function type and a (very abbreviated) usage. To really understand what the function does, you will most likely need to refer to the wxWidgets C++ documentation for the equivalent function, so we’re going to see what that means in practice.

The first thing to realize is that you probably want a minimal ability to read C++, at least enough to understand a function signature and to guess how the parameters map to the Haskell function signature. It is also useful to have a notion of how object oriented design works, since there’s no getting away from the fact that wxWidgets, which underlies wxHaskell, is heavily object-oriented in its design.

Let’s take the example of menuAppend.

The wxHaskell documentation says: menuAppend :: Menu a -> Id -> String -> String -> Bool -> IO () with the further comment “usage: (menuAppend obj id text help isCheckable)”.

Now, there is a naming convention which is followed fairly consistently, and that is that the start of any function name in Graphics.UI.WXCore.WxcClassesXX is the same as the name of the equivalent wxWidgets class with the “wx” prefix lopped off (all wxWidgets classes and names are prefixed “wx” as the design of the library predates C++ namespaces). Once you have read the last sentence through a couple of times, you’ll realize that all I really meant to say is that we should go to the wxWidgets documentation and look for the class wxMenu. Furthermore (and again, this is a consistent naming convention), I am most likely interested in a function which performs an Append() operation on a wxMenu.

When we go to the documentation for wxMenu::Append() we see that there are three variants of wxMenu::Append(). For those who aren’t familiar with C++, I should explain that C++ lets a single function name be overloaded with different parameter types. Haskell doesn’t allow this, so our menuAppend function can only be the equivalent of one of these type signatures.

  • wxMenuItem* Append(int id, const wxString& item = “”, const wxString& helpString = “”, wxItemKind kind = wxITEM_NORMAL) Adds a string item to the end of the menu.
  • wxMenuItem* Append(int id, const wxString& item, wxMenu *subMenu, const wxString& helpString = “”) Adds a pull-right submenu to the end of the menu. Append the submenu to the parent menu after you have added your menu items, or accelerators may not be registered properly.
  • wxMenuItem* Append(wxMenuItem* menuItem) Adds a menu item object. This is the most generic variant of Append() method because it may be used for both items (including separators) and submenus and because you can also specify various extra properties of a menu item this way, such as bitmaps and fonts.

I hope it doesn’t require a “super C++ guru” to realise that the first of the list items above is the closest to our menuAppend function. Those who have really been paying attention may notice that there are actually several functions which start menuAppend, including menuAppendSub and menuAppendItem, and these are actually wrappers for the other two variants of wxMenu::Append(). The only other thing you need to observe to line the parameters up between the C++ and the Haskell versions of the functions is that there is an initial obj parameter in all of the Haskell functions. This is because you would normally use an object pointer or reference in C++ so that the C++ code:

mnuFile->Append(wxID_OPEN, "&Open...\tCtrl-o", "Open Page", 0);

is effectively rendered in Haskell as:

menuAppend mnuFile wxID_OPEN "&Open...\tCtrl-o" "Open Page" False

One other aspect of using the functions in Graphics.UI.WXCore.WxcClassesXX is that we have to care about having unique menu identifiers. The standard menu items (Open, Close, Save and the like) have standard identifiers, and we use them here.

 > mnuFile <- menuPane [text := "File"]
 > menuAppend mnuFile wxID_OPEN "&Open...\tCtrl-o" "Open Page" False
 > menuAppend mnuFile wxID_SAVE "&Save\tCtrl-s" "Save Page" False
 > menuAppend mnuFile wxID_SAVEAS "Save &as...\tCtrl-Shift-s" "Save Page as" False
 > menuAppend mnuFile wxID_CLOSE "&Close\tCtrl-W" "Close Page" False

When creating menu entries the WXCore way, we need to attach event handlers to each item. The evtHandlerOnMenuCommand :: EvtHandler a -> Id -> IO () -> IO () function associates a menu ID in a given window with an event handler.

It’s worth examining evtHandlerOnMenuCommand a little more closely. The first thing to notice is that I said that we associate an event handler with a window and a unique identifier. If you check back over the code, win is of type Frame (), but evtHandlerOnMenuCommand wants an EvtHandler a how does this work?

The underlying wxWidgets library is a piece of OO design in C++, and if you check the wxWidgets documentation for wxFrame (which is what a Frame is under the hood), it tells us that the inheritance hierarchy looks like the following (read ‘->’ as “inherits from”):

wxFrame -> wxTopLevelWindow -> wxWindow -> wxEvtHandler -> wxObject

This, in OO C++ jargon, means that a wxFrame is-a wxEvtHandler. Another way of saying this is that you can treat a wxFrame as a wxEvtHandler.

That’s all very well for C++, but we are working in Haskell, and Haskell doesn’t have objects. It turns out, though, that we can model the hierarchy of an OO design using types (although the approach doesn’t really support multiple inheritance very well).

If you go to the documentation for Frame (in Graphics.UI.WXCore.WxcClassTypes), you will find that the type of Frame turns out to be:

type Frame a = TopLevelWindow (CFrame a)
type TFrame a = TTopLevelWindow (CFrame a)
type CFrame a

This looks a little like the C++ inheritance hierarchy. Checking further:

type TopLevelWindow a = Window (CTopLevelWindow a)
type TTopLevelWindow a = TWindow (CTopLevelWindow a)
type CTopLevelWindow a
type Window a = EvtHandler (CWindow a)
type TWindow a = TEvtHandler (CWindow a)
type CWindow a

Haskell being a nice predictable and pure language, we can do some substitutions, and it turns out that our Frame () can be expressed as:

Frame () = EvtHandler ( CFrame () )

Since the CFrame a constructor doesn’t really do anything (it is called a “type witness”), all of this means that our Frame () is-a EvtHandler a, and we can use it in evtHandlerOnMenuCommand.

The other aspect of the event handlers is that, at least in this case, no useful information is provided by the event, so if you need to pass any information to the event handler, you most likely need to do this by currying the event handler function. In this case, while evtHandlerOnMenuCommand expects an event handler to have type IO (), the event handlers for the menu in this application typically include a curried guiCtx parameter which holds information about the controls and files used in the application.

> evtHandlerOnMenuCommand win wxID_OPEN $ openPage guiCtx
> evtHandlerOnMenuCommand win wxID_SAVE $ savePage guiCtx
> evtHandlerOnMenuCommand win wxID_SAVEAS $ savePageAs guiCtx
> evtHandlerOnMenuCommand win wxID_CLOSE $ windowClose win False >> return ()

The remainder of the function is pretty similar to step 1, except that we need to add the menu bar to the Frame by setting the menuBar property.

> set win [menuBar := [mnuFile]]
> set win [layout := fill $ widget editor, clientSize := sz 640 480]
> focusOn editor
> set win [visible := True]

Event Handlers

Much of the functionality of a GUI application in most widget toolkits is executed in response to events. A wxHaskell application is no exception to this rule, and much of the logic of any application you develop will reside in its event handlers.

The event handling functions below all have type GUIContext -> IO (), with the GUIContext carrying shared state information.

The openPage function is responsible for loading a file into the editor pane. In common with most GUI toolkits, wxHaskell provides the ability for the programmer to use standard dialog boxes for key functions such as loading and saving files, and some of the convenience functions provided make the use of these pretty straightforward. The fileOpenDialog function has the following signature:

fileOpenDialog :: Window a -> Bool -> Bool -> String
               -> [(String, [String])] -> FilePath
               -> FilePath -> IO (Maybe FilePath)

The parameters, in order, have the following purposes:

  • Parent window identifier
  • Bool which, if true, indicates that the application should remember the last selected directory.
  • Bool which, if true, indicates that read-only files can be selected
  • String containing the text for the dialog box frame
  • A list of tuples which define the filename selections offered by the dialog box. Each tuple (String, [String]) is a pair in which the first element is a String containing a description of the file type and the second element is a list of wildcard patterns denoting acceptable file extensions.
  • A String indicating the path to the initial directory (often set as the empty string, which indicates no default directory)
  • A String containing the default filename to choose (also often set to the empty string, which indicates no initial selection)

The result of invoking fileOpenDialog is a Maybe FilePath. If we have Nothing, then no file was selected and we simply return without doing anything.

If we have a Just path in which path is the complete path to the selected file, then we load the selected file into the text control, set the title of the Frame to include the filename loaded in the text control and remember the file location in the filePath mutable variable.

There are two ways in which you could load text into the TextCtrl, guiEditor. The first is to use normal Haskell file handling functions to load the file contents into a string and assign the text property of guiEditor to contain the string. The second, used here, is to use the WXCore function textCtrlLoadFile. I’ll also point out, once more, that the text property of a Frame (in this case guiWin) sets the text at the top of the Frame window.

> openPage GUICtx{guiWin = win, guiEditor = editor, guiFile = filePath} =
> do
>   maybePath <- fileOpenDialog win True True "Open file..."
>                               [("Haskells (*.hs)",["*.hs"]),
>                                ("Texts (*.txt)", ["*.txt"]),
>                                ("Any file (*.*)",["*.*"])]
>                               "" ""
>   case maybePath of
>     Nothing   -> -- The user cancelled... nothing to do
>                  return ()
>     Just path -> do
>                  textCtrlLoadFile editor path
>   set win [text := "wxhnotepad - " ++ path]
>   varSet filePath $ Just path

The function to save a file is very similar in structure to openPage. There is a convenience function fileSaveDialog which lets you select the name of a saved file using the standard file dialog for your platform, and a function textCtrlSaveFile which lets you save the contents of a text control to a file.

> savePageAs GUICtx{guiWin = win, guiEditor = editor, guiFile = filePath} =
> do
>   maybePath <- fileSaveDialog win True True "Save file..."
>                               [("Haskells (*.hs)",["*.hs"]),
>                                ("Texts (*.txt)", ["*.txt"]),
>                                ("Any file (*.*)",["*.*"])]
>                               "" ""
>   case maybePath of
>     Nothing   -> return ()
>     Just path -> do
>                  textCtrlSaveFile editor path
>                  set win [text := "wxhnotepad - " ++ path]
>                  varSet filePath $ Just path

The savePage function is a simple wrapper around savePageAs for the case when we want to save a file to the existing filename. The current filename is fetched from the filePath mutable variable. We use a guard to verify that we do, in fact, have a filename set allowing the save operation to be executed, and if we do not, we call savePageAs to pull up a dialog box.

> savePage guiCtx@GUICtx{guiWin = win, guiEditor = editor, guiFile = filePath} =
> do
>   maybePath <- varGet filePath
>   case maybePath of
>     Nothing   -> savePageAs guiCtx
>     Just path -> textCtrlSaveFile editor path >> return ()

An interesting reader exercise would be to modify the menu so that the savePage menu is only enabled when a filename is set. You will probably want the menuItemEnable function to assist in this modification. In this case the menu item would only be available when we have a filename, and the call to varGet filePath should always return a filename.

That completes step 2 of the text editor. Next time we will add undo / redo functionality.

Building a text editor (Part 1)

Edit: added cabal install information. Thanks Slaava!

This is the first post in a new series, aimed at wxHaskell beginners.

I did not write the code in this post. It was written by Fernando Benavides especially for this blog, and I’m extremely grateful for his help. The code is BSD3 licensed and under his copyright. You can fetch it as a cabal package (update: cabal install wxhnotepad), which is the best way to follow this tutorial. The fact that Fernando wrote the code means that in case of any disagreement between my commentary and the code, you should believe the code 🙂

I should also mention that Fernando is the author of λpage, which he describes as a Haskell scrapbook – you can think of it as a GUI-based and more featureful GHCi. It has several neat features: Hayoo integration and the ability to determine the kind of types are two stand-outs for me. I enjoyed checking it out, and find myself using it quite often. See what you think.

The first step in the tutorial is just about the most minimal wxHaskell application imaginable: a text editor without the ability to load or save text, no search and no replace. It’s a good start though, and in the next few posts it will develop into a usable notepad replacement.

Fernando has written the code in a particularly neat way – there are actually six versions of the editor, and you can call any of them from the main launcher screen. We’ll start with the launcher, since it is the main module for the program.

The Launcher

There are two libraries which make up wxHaskell:

  • WXCore, a fairly thin wrapper around wxWidgets (the C++ library which does most of the rendering). The functions in WXCore tend to require a style of programming similar to C++, although we at least benefit from Haskell type inference when using them.
  • WX, a higher-level library which enables a more declarative style of programming. As a general rule, you will probably want to use WX functions whenever possible and drop down to WXCore when WX does not do what you need. You will actually need to do this relatively often, as there are quite a few useful features in WXCore which do not have equivalents in WX.

At the top of any wxHaskell program, you will almost certainly want to import WXCore and WX, so:

> module Main where
>
> import Graphics.UI.WX
> import Graphics.UI.WXCore
>
> import Step1
> import Step2
> import Step3
> import Step4
> import Step5
> import Step6

Like every other Haskell program, wxHaskell applications start with main.

In this case we have a very simple main program, but in a more complex application you might have come command line option handling, configuration file handling or similar. However, the essential part of a wxHaskell application is a call to start with a sequence of IO actions which make up the GUI logic of your program.

For wxHaskell application programming, that’s all you really need to know about start-up, but for the curious (or those who have done some wxWidgets programming in C++), what is happening under the hood is that start creates an instance of a wxHaskell application class derived from wxApp and this instance uses the closure represented by gui in the implementation of wxApp::onInit().

> main :: IO ()
> main = start gui

The launcher is very simple. It consists of a Frame which has a menu and nothing else.

Any wxHaskell application requires a top level container window. This is almost always a Frame, although it is possible to use a Dialog as a container if you have a very simple form-type GUI in mind. If you want a menu, you will definitely need a Frame, and we want a menu.

It is worth a closer look at how the Frame is created and configured, since this is a model for creating many windows and controls in wxHaskell. The wxHaskell documentation for frame says that is has type frame :: [Prop (Frame ())] -> IO (Frame ()), and that it creates a top level frame window.

What does this [Prop (Frame ())] mean? Well, wxHaskell has a mechanism which lets you perform much of the configuration of the different window and widget types in a declarative fashion by setting (or reading back) Attributes. This is much nicer than mucking about with lots of individual functions, and tends to create code which is clear and easy to understand.

The precise meaning of [Prop (Frame ())] is that you may provide a list of Properties which are applicable to a Frame. Most of these properties have been grouped into typeclasses, and the documentation usually indicates which are supported by a given type (the usually here should be taken to say that if you try this for Frame, you will be disappointed to find out that the documentation doesn’t mention this at all…)

  • The text attribute is typically used to manipulate some form of meaningful text in a control. In the case of a Frame it sets the text in the window frame; in the case of a static text or text control it sets the text in the control.
  • The visible attribute is supported by most controls – it determines whether the control is visible or not.
  • The on attribute is more interesting. It is typically followed by an event name, and the pair is used to configure an event handler.

Thus, the short snippet of code below creates a Frame with the caption “wxhNotepad”, which is initially invisible and which calls a function, wxcAppExit when the Frame closing event is fired.

One other point of note: the set function can be used to set or change the properties of a window or control which has already been created (there is a related get function for reading values back as well). In this case we could have put the closing event handler into the property list we used when creating the frame, but in some cases (e.g. when you need to know the control identity to configure things correctly), you will need to use this
two (or more) phase approach.

 > gui :: IO ()
 > gui =
 >   do
 >     win <- frame [text := "wxhNotepad", visible := False]
 >     set win [on closing := wxcAppExit]

The say function is a convenience for launching a small information dialog box.

 > let say title desc = infoDialog win title desc

The main purpose of the launcher is to support the menu which lets you use the editor in each of its stages of development. There are a couple of ways of creating a menu (we’ll see the lower-level way later).

The simplest is to use menuPane to create a menu heading (e.g. ‘File’), menuItem to create an item in a menu (e.g. ‘Open’) and menuBar to set the menu for a frame. There are convenience functions for certain menu entries, notably the ‘Help’, ‘About’ and ‘Quit’ menu items, as these may require special handling on certain OS platforms, and using the convenience function ensures that you do this in the way expected on each OS.

It is worth quickly noting that for menu items, the text property is used for the menu text. Notice also that menu shortcuts and accelerators can be defined in the menu text itself. The wxWidgets documentation for wxMenu::Append() describes this format in detail.

 > mnuSteps <- menuPane [text := "Steps"]
 > menuItem mnuSteps [on command := step1,
 >    text := "Step &1 - Just a Text Field\tCtrl-1"]
 > menuItem mnuSteps [on command := step2,
 >    text := "Step &2 - Open / Save / Save As...\tCtrl-2"]
 > menuItem mnuSteps [on command := step3,
 >    text := "Step &3 - Undo / Redo...\tCtrl-3"]
 > menuItem mnuSteps [on command := step4,
 >    text := "Step &4 - Cut / Copy / Paste...\tCtrl-4"]
 > menuItem mnuSteps [on command := step5,
 >    text := "Step &5 - Find / Replace...\tCtrl-5"]
 > menuItem mnuSteps [on command := step6,
 >    text := "Step &6 - Toolbar / Statusbar / Context Menus\tCtrl-6"]
 > menuQuit mnuSteps [on command := wxcAppExit]
 >
 > mnuHelp <- menuHelp []
 > menuAbout mnuHelp [on command := say "About wxHNotepad"
 >       "Author: Fernando Brujo Benavides\nWebsite: http://github.com/elbrujohalcon/wxhnotepad"]

Once we have created a menu, it needs to be assigned to our Frame, and this is done with the menuBar property mentioned earlier. Notice that the menuBar takes a list of menuPane instances.

We finally make the Frame visible. There’s a neat trick to note here: what we are trying to do is to create a Frame which contains nothing but a menu. This is no problem on OSX, but Windows and Linux don’t really support it. However, if you set the clientSize property of the Frame to (0,0) then you get much the same effect.

 > set win [menuBar := [mnuSteps, mnuHelp],
 > visible := True, clientSize := sz 0 0]

Text editor: step 1

This is the absolutely minimal, first stage text editor. It consists of nothing more than a text control inside a Frame. No menu. No dialogs and no real functionality. Perhaps the only aspect of interest is to note that
it is easy to make a wxHaskell application with more than one Frame, should you wish to.

Since this is the second time we have mentioned clientSize, it is probably worth a moment to explain what this means. There are several different ways to look at the size of a window. Two of the
most important are:

  • clientSize The size available for displaying information inside a window – i.e. if the clientSize is (640, 480), this means that there are 640 x 480 (width x height) pixels available for displaying information. Borders, window decorations and so on take up additional space.
  • virtualSize The size which would be needed to display all of the information contained in the window. Often the clientSize and virtualSize are the same, but if there is more information in the window than can be displayed fully (i.e. if you need a scroll bar) then the clientSize will be smaller than the virtualSize.

There is one new call in the snippet below: textCtrl constructs a text control. As parameters it requires a parent window (which in this case will be the Frame, win) and a list of properties. All non top-level windows require their parent as a parameter, since wxWidgets keeps windows in a hierarchy rooted at the top-level.

 > step1 =
 > do
 > win <- frame [text := "wxhNotepad - Step 1", visible := False]
 >
 > editor <- textCtrl win [font := fontFixed,
 >           text := "This is our first step in the " ++
 >           "developing of our text editor.\n" ++
 >           "Just a big text area where " ++
 >           "the user can read and write text\n" ++
 >           "That's not much, but it's just the " ++
 >           "beginning..."]

In the following snippet, we use the Layout mechanism to help us to fit our textCtrl inside the frame.

Layout is a conceptually elegant mechanism which allows you to describe the way in which the windows in an application are arranged and organized in a declarative manner.

The reality is that some aspects of the way that Layout works are rather complex and subtle (so much so that Layout will probably be the subject of a blog article or two of its own in the near future), but in this demonstration, Layout will work very well for us. I’d just ask that you don’t get discouraged if you have issues with more complex arrangements of controls using Layout.

Layout is specified using the layout property. It consists of a sequence of combinator functions which must ultimately resolve to a Attr w Layout type. For the moment, we just need to know that:

  • widget requires a control as a parameter. It indicates how the specified control should be placed in the Layout.
  • fill is a Layout transformer which indicates that the Layout to which it is applied should stretch and expand into the available area.

The documentation for Layout will give a better feel for what is happening, if you would like to understand more, but please bear in mind that this is a fairly complex subject, since what Layout is actually doing is to create sizer instances from the Layout specification, and sizers are a fairly large subject in themselves.

 > set win [layout := fill $ widget editor,
 >          clientSize := sz 640 480]
 >
 > focusOn editor
 >
 > set win [visible := True]