Cursors, Part 2: The text cursor

Date 2018-11-28

This is the second post in a series about cursors. It prepares the right data structure to write an editor for a single line of text.

Disclaimer: cursor is a library based off the concepts outlined in this blog post. It originated in the work on smos, a Purely Functional Semantic Editor.

Motivation: A text cursor separate from a list cursor

A text cursor is a cursor for a single line of text. One could be tempted to define a text cursor as a specific case of a list cursor:

type TextCursor = ListCursor Char

However, this is problematic when we are trying to describe pieces of text that fit on one line. Here is an example of an invalid TextCursor according to the above synonym:

ListCursor
  { previous = "hello\n"
  , next = "world"
  }

Indeed, there must not be any newlines among the characters in the cursor. If there were CharacterThatIsNotANewline type, then we could use that, but in the absence of such a constrained version of Char, we will opt for testing instead of typing. This presents a nice opportunity to show off validity-based testing.

The best way to deal with this problem is to wrap ListCursor Char in a newtype as follows:

{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics (Generic)
newtype TextCursor = TextCursor
  { unTextCursor :: ListCursor Char }
  deriving (Show, Eq, Generic)

, add an internal variant to it using a Validity instance.

import Data.Validity

instance Validity TextCursor where
  validate (TextCursor lc) = mconcat
    [ genericValidate lc
    , decorateList (rebuildListCursor lc) $ \c ->
        declare "The character is not a newline character" $
          c /= '\n'
    ]

Here, genericValidate takes care of recursing into the newtype in case ListCursor Char would have any internal invariants because then they should also be satisfied. The decorateList :: [a] -> (a -> Validation) -> Validation function allows us to specify how to validate all elements of a list using some nice decoration in the error message. Here we specify that the characters in the underlying ListCursor must not be newlines.

Now we can use validity's constructValid :: Validity a => a -> Maybe a to make a smart constructor:

makeTextCursor :: Text -> Maybe TextCursor
makeTextCursor = constructValid . makeListCursor . T.unpack

This way, we do not have to define any of the invariant checking twice.

Example manipulation functions and testing

Most of the functions to manipulate TextCursors can be define to defer to the corresponding functions for ListCursor Char. To make sure that this actually produces correct results, we set up some validity-based tests.

First we need to define generators for TextCursor. Because TextCursor has a Generic instance, that involves no more than the following single line:

instance GenUnchecked TextCursor

Now we have a generator (genUnchecked) that can generate TextCursors that aren't necessarily valid. The next line then gets us a generator for valid values (genValid):

instance GenValid TextCursor

Incidentally, these two lines also get us free shrinking for TextCursors (shrinkUnchecked and shrinkValid).

Now we can test the relevant functions, textCursorInsert :: Char -> TextCursor -> TextCursor for example, to make sure that it maintains the TextCursor invariants:

import Test.Validity
import Test.Hspec

describe :: Spec
desrcibe = do
  describe "textCursorInsert" $ 
    it "produces valid text cursors" $
      producesValidsOnValids2 textCursorInsert

When we run this test suite, we soon notice that inserting a '\n' character into a TextCursor produces an invalid TextCursor. This must not happen, so we change the type to allow for failure: textCursorInsert :: Char -> TextCursor -> Maybe TextCursor and allow textCursorInsert to fail:

textCursorInsert :: Char -> TextCursor -> Maybe TextCursor
textCursorInsert '\n' _ = Nothing
textCursorInsert c tc = Just (tc & textCursorListCursorL %~ listCursorInsert c)

References

Text cursors are available in the cursor package on Hackage. Cursors originated in the work on Smos. This post is part of an effort to encourage contributions to Smos. The simplest contribution could be to just try out smos and provide feedback on the experience. Smos is a purely functional semantic editor of a subset of YAML that is intended to replace Emacs' Org-mode for Getting Things Done.

Previous
Picosmos: Writing a simple single-line text-editor with brick.

Looking for a lead engineer?

Hire me
Next
Announcing Validity version 0.9.0.0: Validity of Double