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

One thought on “Building a text editor (Part 5)”

Leave a comment