Formlets are biapplicative

Formlets are great but they conflate model and view. Existing approaches to separation using holes are suboptimal and untyped. Biapplicative functors allow to compose forms in a clean and type-safe fashion with full separation of model and view code.

I found myself writing GUIs in Haskell with threepenny-gui for my employer recently. This was a great opportunity to learn more about FRP and I stumbled upon an unexpected neat trick. The trick is best explained in the context of formlets.

Formlets

Formlets are a functional abstraction around HTML input forms, based on the idea of using Applicative functors there where Monads could not venture to compose the fragments, so called formlets, of a form.

In the original paper a formlet composition defines two things:

  1. a data validation and composition procedure, and
  2. a UI component.

This can result in overcrowded definitions, as seen on the date example from the paper (adapted and simplified):

data Date = Date {month, day :: Int}

dateFormlet :: Formlet Date
dateFormlet = 
  tag "div" [] (Date <$> (text "Month:" *> input_int) 
                     <*> (text "Day:" *> input_int <* text "\n"))

Contexts

The paper did highlight this issue and proposed the use of “multi-holed contexts” to separate model and UI code, adding a “context” language for defining UIs with:

  • a hole primitive to mark the occurrences of formlets.
  • a plug run function that takes a context expression and a formlet and fills in the holes with the formlet components to produce a UI.

The date example with contexts looks like follows, where XML nodes have the obvious Monoid instance:

dateFormlet = 
  plug 
    -- UI 
    (tag "div" [] (text "Month:" <> hole <> text "Day:" <> hole <> text "\n") 
    -- model
    (Date <$> inputInt <*> inputInt))

The context language made use of a parameterized applicative functor to keep count of the number of holes, but the holes themselves were untyped, so the typechecker’s help was limited. Moreover, there was no binding between a hole and its formlet, so plug would simply fill the holes in order. The only guarantee being that all the holes in the UI template get filled.

Digestive functors

Modern Haskell implementations of formlets like the digestive-functors package do provide this separation, but eschew the complex hole counting in favour of an untyped string-based addressing scheme.

The digestive-functors tutorial section on Views may slightly disturb a seasoned Haskell programmer.

Biapplicative functors

Biapplicative functors are bifunctors which support applicative composition on both arguments. The bifunctors package contains the following Haskell encoding of this abstraction:

class Bifunctor p => Biapplicative p where
  bipure  :: a -> b -> p a b
  (<<*>>) :: p (a -> b) (c -> d) -> p a c -> p b d

The practical difference w.r.t. standard applicative functors is that bipure takes two arguments and performs a parallel composition. For a simple example, let’s use the Biapplicative instance for tuples:

> bipure (++) (+) <<*>> ("123", 123) <<*>> ("456", 456)
("123456",579)

Biapplicative formlets

A Formlet is essentially a tuple of HTML nodes defining a Form, and a callback that produces a value. The original Formlet definition was parametric only on the return type of the callback, i.e. the type of the value produced after a successful interaction with the user. The key insight is to reveal the biapplicative structure by making the Formlet type parametric on the UI type as well.

data Formlet ui a
data HTML
instance Biapplicative Formlet

-- ‘inputInt’ is a Formlet with an HTML UI that produces an Int value 
inputInt :: Formlet HTML Int

In order to compose biapplicative formlets, bipure expects a function to compose the UI values and a function to compose the return values. We could simply use HTML primitives to compose the UI values, but another option is to use a datatype constructor to bind the UI components. Therefore we define a new datatype DateForm and a function renderDateForm :

-- | A form to edit values of type 'Date'
data DateForm = DateForm {day, month :: Input Int}

-- | The logic side
dateFormlet :: Formlet DateForm Date
dateFormlet = bipure DateForm Date <<*>> inputInt <<*>> inputInt

-- | The UI side
renderDateForm :: DateForm -> HTML
renderDateForm DateForm{..} = 
    tag "div" [] (text "Month:" <> month <> text "Day:" <> day <> text "\n")

If, as in this case, the form type has the same shape as the value type, we can define both in the same declaration with a little type level machinery:

{-# LANGUAGE TypeFamilies, DataKinds #-}
class Editable a where
  type EditorWidget a
  editor :: Formlet (EditorWidget a) a

instance Editable Int where
  type EditorWidget Int = HTML
  editor = inputInt

data Purpose = Model | View

type family Field (purpose :: Purpose) a where
  Field 'Model  a = a
  Field 'View a = EditorWidget a

With this machinery in place we can redefine Date as a dual purpose datatype, being used both for model and view purposes. The DateForm boilerplate definition is gone and the final version of the Date example is simply:

data Date purpose = Date { day, month :: Field purpose Int}

dateFormlet :: Formlet (Date View) (Date Model)
dateFormlet = bipure Date Date <<*>> editor <<*>> editor

To wrap up, biapplicative functors provide a fully typed solution to separate model logic from UI, by binding the component widgets to function arguments. This is achieved without compromising type inference or requiring fancy type extensions. Turning a few of those on, we can reuse the datatype declarations and keep the boilerplate down to a minimum.

Threepenny-editors

These days Forms are giving way to fully interactive JavaScript UIs, but undoubtedly the lessons of Formlets still apply. Threepenny-gui provides a set of FRP and HTML primitives but not much guidance on how to compose them. Reading through the lines, a design pattern for a Form-like approach to editors emerges. An editor-let is a function from an input Behavior to a tuple of an HTML node and a composable event tiding:

newtype Editor in html out = Editor (Behavior in -> (html, Tidings out))

The in variable is contravariant in Editor, and both html and out are functorial and applicative. Which means of course that Editor must be a biapplicative profunctor, right?

The code for composing dual purpose editors is completely mechanic and can be derived via generics leading to very little else than the datatype declaration:

data PersonF (purpose :: Purpose) = Person
  { education           :: Field purpose Education
  , firstName, lastName :: Field purpose String
  , age                 :: Field purpose (Maybe Int)
  }
  deriving Generic

type Person = PersonF Model
type PersonEditor = PersonF View


instance Editable Person where
  type EditorWidget Person = PersonEditor
  editor = editorGenericBi

The UI is defined separately as desired:

instance Widget PersonEditor where
  getElement Person{..} =
    ( ("First: "  ||| firstName) ===
      ("Last: "   ||| lastName)  ===
      ("Status: " ||| status)
    ) |||
    (("Age:" ||| age) ===
     ("Brexiteer: " ||| brexiteer) ===
     ("Education: " ||| education))
   where
    (|||) = horizontal
    (===) = vertical

A fully worked development of this approach can be found in the threepenny-editors package. Feedback and contributions are always welcome.

Previous art

In the process of writing this post I googled for “biapplicative” and “biapplicative formlets”, and it turns out that someone else already figured this trick out! The reform package for the venerable Happstack framework already used Bifunctors, albeit under a different name and for a slightly different purpose, validation instead of UI composition.

Monadic stack traces that make a lot of sense

Call traces are a recurrent topic in the Haskell community. Nearly every programming language out there has this feature, except Haskell. For an imperative language providing stack traces is easy, since the runtime stack contains all the information needed, and it can be retrieved essentially for free. But in a lazy language the stack does not contain call frames, and hence providing a “stack trace” is a much more involved task. As existing efforts we can cite the -xc flag of the GHC profiling runtime, which provides a stack trace based on cost centers; and the GHCi debugger :trace command which records a lazy call trace. There is also the Hat tool which is capable of providing a post-mortem stack trace via a program transformation, but I don’t know if you can make Hat work nowadays. And the not yet released tool for GHC presented by Tristan Allwood in the Haskell Symposium(video). With exception of the latter, which is not yet available, I believe that all these options are not really solving the lack of stack traces in practice.

While working on the control-monad-exception and by suggestion of Jeff Heard I have been looking at providing exception call traces. That is, making a call trace available to an exception handler. This can be very useful to give more detailed error messages which help to diagnose a problem in our code. For instance, recall the example in my previous post.

data ProcessError = NotThreeLines String
   deriving (Show, Typeable) 
instance E.Exception ProcessError

process :: FilePath -> AttemptT IO Int 
process filePath = do
       contents <- A.readFile filePath
       case lines contents of
           [num1S, opS, num2S] -> do
               num1 <- A.read num1S
               op   <- A.read opS
               num2 <- A.read num2S
               return $ toFunc op num1 num2
           _ -> Failure $ NotThreeLines contents

A.read is a custom version of read which throws an exception if Prelude.read fails to read its argument. There are three different source code locations in which A.read may fail in the body of process. Getting a ReadFail exception is not going to tell you *which* read attempt failed, in the same way that a “head of empty list” error does not tell you which call to head of all the calls to head in your program failed. With support for exception call traces, you could get an error message for this exception that looks like this:

error: ReadFail: could not read the String ....
  in Main.hs: line 27, col 20
  in ...
  in ...
  in Process.hs: line 12, col 15

This is not possible right now. None of the libraries for exceptions in Hackage support this kind of call traces. Admittedly, the situation is not as bad as the “head of empty list” case, because if you are using a version of head that throws an exception, chances are high that the exception will be captured close enough to the call site that it is clear where the error is coming from. But still, anything below this level of error reporting is substandard in a modern programming language.

In this post I show how a standard Error monad can be extended to carry call traces. An error monad in Haskell can be implemented by the Either datatype, a suitable Monad instance, and a pair of throw and catch functions. The Left constructor denotes an exception, defined here as the SomeException type in ControlException, and the Right constructor denotes a succesful computation. Omitting unessential cruft the code looks like:

type ErrorM a = Either SomeException a
throw :: e -> ErrorM a 
throw = Left 

instance Monad (Either e) where
   return = Right
   Left  e >>= _ = Left e
   Right v >>= f = f v 

catch :: Exception e => ErrorM a -> (e -> ErrorM a) -> ErrorM a
catch (Right v) _ = Right v 
catch (Left e) h = ...

Nothing surprising here. I omitted part of the implementation of catch because it is slightly more involved due to the existential machinery that makes SomeException work.

We want to extend this interface with a function catchWithCallTrace which provides access to the call trace. Something with a signature

catchWithCallTrace :: Exception e => ErrorM a -> (e -> [SrcLoc] -> ErrorM a) -> ErrorM a
type SrcLoc = String

where SrcLoc is some abstract datatype for source code locations. In this case a simple String suffices.
To generate this call trace, the first step is to extend our ErrorM monad to keep a list of source code locations in the Left constructor.

type ErrorM a = Either (SomeException, [SrcLoc]) a

The next step is modify the definition of bind so that it inserts the current source code location in the call trace whenever it spots an exception.

Left (e, trace) >>= f = Left (e, <currentloc> : trace)

In this way whenever the exception reaches a handler, it will find a list of SrcLocs starting from the throw site all the way up to the handler site stored in the computation. This constitutes a monadic call trace, which due to the order of evaluation imposed by the Either monad, resembles very closely a stack trace from an imperative language. This is great, because that is exactly the kind of call trace that makes sense to the programmer. I have been testing the library with a small personal project involving a CGI applet and a database, and the capture below shows the kind of error output that my CGI applet provides.

The implementation of catchWithCallTrace now is straightforward.

catchWithCallTrace (Left (exception, trace)) h = h exception trace

The above line is pseudocode since it omits the handling of the existential stuff for SomeException, but it conveys the idea.
All what is missing now is to turn the equation for (Left e >>= f) above into real Haskell. Those source code locations must be made available to (>>=). This is not possible in the standard definition of (>>=), so we extend the Monad type class with a bindWithSrcLoc method, polluting its categorical elegance with the concerns of mundane coders.

class Monad where
   ...
   bindWithSrcLoc :: SrcLoc -> m a -> (a -> m b) -> m b
   bindWithSrcLoc _ = (>>=)

This is a conservative extension which breaks no existing code and has no performance penalty. There is a default implementation which ignores the source location and calls bind, and there should be no performance penalty at all for using bindWithSrcLoc in a regular monad which does nothing with src locs, if we can trust GHC to inline the body of (>>=) in the default definition.

For the ErrorM monad we give bindWithSrcLoc a different implementation:

instance Monad ErrorM where
   ...
   bindWithSrcLoc srcloc (Left (e, trace)) _ = Left (e, srcloc:trace) 
   bindWithSrcLoc srcloc (Right x) f = f x

That is all what is needed to provide monadic call traces. In order to make programming with bindWithSrcLoc feasible, Haskell compilers can desugar do-notation using the bindWithSrcLoc variant, providing accurate source code locations which are available at “desugaring time”. Yes, this means that do-notation stops being mere syntactic sugar to become something more, but I perhaps it is a small price to pay if we gain monadic call traces in the process? Once there is support for this in the compiler, any monad can implement this interface and provide this facility, including the IO monad, the ErrorT monad transformer from the mtl package, and any other error handling monad.

To wrap up this post, I am making available an experimental implementation of monadic call traces with the 0.5 release of control-monad-exception. Obviously I can’t just extend the Monad class in a package, so the mechanism used in this release is not as elegant as the one presented here. It uses a MonadLoc class to deal with source code locations and includes the MonadLoc preprocessor, a tool based on haskell-src-exts (thanks Niklas for such an awesome library, the entire code for the preprocessor fits in a few lines of haskell) which makes the source code locations happen in the right places. When, if ever, the Monad class is extended to provide source locations, the MonadLoc preprocessor will no longer be needed. But in order to get monadic stack traces now, all you need to do is to use the Control.Monad.Exception.EMT monad in you code and insert the following pragma at the top of your files:

{-# OPTIONS_GHC -F -pgmF MonadLoc #-}

I should also mention that nothing in the monadloc package is specific to control-monad-exception. Any other monad can implement the MonadLoc type class and benefit from the MonadLoc preprocessor to provide monadic call traces.

Enjoy your Haskell monadic call traces!

control-monad-exception and the long type signatures myth

Yesterday Michael Snoyberg blogged a tutorial about his Attempt package for Haskell error handling. This inspired me to port his example to my control-monad-exception library and see how well it works.The main difference between the two libraries is that Attempt provides extensible exceptions which are not explicit whereas control-monad-exception’ exceptions are explicit and checked by the type system a la Java. Under the hood they are very similar, Both are monads based on a datatype isomorphic to Either instantiated with extensible exceptions, but control-monad-exception has some extra oomph to make the typechecker understand exception handling. Michael dismisses control-monad-exception arguing that explicit exceptions produce “insanely long type signatures”. Since I don’t agree on that, I hope to support my point with this blog post.

His tutorial introduces an example about text processing to illustrate the use of Attempt: you want to parse text files which should contain three lines, each line containing an arithmetic expression of the form line  ::= <num> <op> <num>. Easy enough, the following Haskell program (copied from his blog) does the job:

> process1 :: FilePath -> IO Int
> process1 filePath = do
>   contents <- readFile filePath -- IO may fail for some reason
>   let [num1S, opS, num2S] = lines contents -- maybe there aren't 3 lines?
>       num1 = read num1S -- read might fail
>       op   = read opS   -- read might fail
>       num2 = read num2S -- read might fail
>   return $ toFunc op num1 num2

Michael explains very clearly why each of those lines may fail and then goes on to replace the unsafe functions by their Attempt equivalents:

  • read is a partial function; it is replaced by a total function in an Attempt monad read’ :: AttemptMonad m => String -> m a
  • readFile is an IO function which can take an exception. It is replaced by a version in the Attempt monad.
  • the pattern matching is replaced by an assertion; I didn’t understand the motivation and think the resulting code is a bit more difficult to understand so I will skip this part.

You do that and the result is the following code.

> data ProcessError = NotThreeLines String   deriving (Show, Typeable)
> instance E.Exception ProcessError
> process :: FilePath -> AttemptT IO Int
> process filePath =>       contents <- A-readFile filePath
>       case lines contents of
>           [num1S, opS, num2S] -> do
>               num1 <- A.read num1S
>               op   <- A.read opS
>               num2 <- A.read num2S
>               return $ toFunc op num1 num2
>           _ -> Failure $ NotThreeLines contents

The resulting code is safe. Running it produces either a Success or a Failure, but can never end with a runtime exception. Now, let’s look at doing the same with control-monad-exception (abbreviated c-m-e from here). First, we need to define safe versions of read and readFile. The c-m-e library provides a type class MonadThrow for computations which may raise an exception.

> safeRead :: (MonadThrow ReadException m, Read a) => String -> m a
> safeRead s = case .. of
>               [x] -> return x
>                _  -> throw $ ReadException s

I omitted the implementation since it is fairly routine and could live in a library. The interesting thing is that the inferred type signature documents the fact that a ReadException can be thrown. Compare it with the type signature of theversion of read in the Attempt library:

> attempRead :: (MonadAttempt m, Read a) => String -> m a

The c-m-e version is not really that much longer after all. The corresponding c-m-e safe version for readFile has the type signature

> readFile :: (MonadIO m, MonadThrow IOException m) => FilePath -> m String

which again is not too bad. Note also that these functions are not defined in any library, since the c-m-e package currently provides only the exception monads and some support combinators. More on that now.

The nice thing at this point is that we haven’t commited to a particular monad. c-m-e provides a monad transformer EMT which can be used for checked, explicit exceptions, but there are also MonadThrow instances for IO and Either which can use the error handling capabilities of those monads as well – and yes, those MonadThrow constraints will go away and you will be back in the world of unchecked and unexplicit exceptions, if that’s what you want-. A MonadThrow instance for Attempt could be easily provided too, and in that way we could have all these safe functions in an independent package which can work with any error handling monad, be it attempt, c-m-e, explicit-exceptions or the IO monad. Please, we must have this.

Ok, enough rambling, back to the example. As you can imagine, the code for the process function is going to be exactly the same as before, modulo the function names. Except that now the type signature is not fixed to any particular monad:

> process :: (MonadIO m, MonadThrow IOException m, MonadThrow ReadException m)
>              => FilePath -> m Int

This is an inferred type signature and one which you would not write yourself normally, as in general you would be working inside a particular monad, not just any monad m. If this monad happens to be the Attempt monad, you would obtain exactly the type signature that we had above:

> process :: FilePath -> AttemptT IO Int

Which is appreciablily shorter. This tells you that process is a computation which can be run and produce either an Int or fail with an (undocumented) error. On the other hand, if you use EMT from the c-m-e package, the following inferred short-enough type signature tells you

> process :: (Throws IOException l, Throws ReadException l)
>              => FilePath -> EMT l IO Int

that process is a computation which can be run and may fail with an IOException or a ReadException. We can go ahead and define a new version of process which handles the IOException:

> process1 s = process s `catch` (e::IOException) -> return (-1)

And now the compiler *knows* that process1 has the type:

> process1 :: Throws ReadException l => FilePath -> EMT l IO Int

as expected. This is the main idea behind the c-m-e library: using the typechecker to track which exceptions have not been caught yet. Type signatures should not grow unwieldly long, unless your code is sloppy and has lots of unhandled exceptions around.

I am going to leave it at here. Michael’s tutorial goes on and wraps the exceptions into the domain exceptions BadIntException and BadOpException, which should always be done.

The c-m-e library provides also other niceties such as stack traces and selectively unchecked exceptions. I encourage you to look at the documentation for the package if you are interested on doing proper error handling in Haskell.