In my opinion, digestive-functors
is needlessly complicated and obscure
(like many Haskell libraries are). It took me three hours to understand how
to work with it. However, until things like forma
get more popular,
that's what we have to work with, I guess. (Oh, and forma
is kinda obscure
too, though a bit less.)
I believe that the best way to understand something is to write your own
version of it, and with digestive-functors
it is seemingly the only way
to understand it. Loading the examples into GHCi shouldn't be necessary,
just read the explanations.
We want to be able to write forms like this:
userForm = User
<$> "name" .: text Nothing
<*> "mail" .: check "Not an email address" checkEmail (text Nothing)
And then we want to be able to do two vastly different things with them:
-
Ignore all logic in the form and just render its structure.
-
“Run” the form against a list of (field, value) pairs and produce a
User
as the result.
And now, a spoiler: whenever you want to be able to run something and to
inspect the structure, it's often going to look like something from the
Free
-land. In our case, we can simply create a data type with special
constructors for pure
and <*>
, and that will give us a way to represent
all form definitions in an inspectable way.
Here's a simplified version of Form
from digestive-functors
:
{-# LANGUAGE GADTs #-}
import Data.Text (Text)
type Name = Text
data Form a where
Pure :: a -> Form a
Ap :: Form (b -> a) -> Form b -> Form a
TextField :: Name -> Text -> Form Text
Checkbox :: Name -> Bool -> Form Bool
In case you are not familiar with the GADTs syntax, it's the same as:
data Form a
= Pure a
| Ap (Form (b -> a)) (Form b)
| TextField Name
| Checkbox Name
The difference is that the GADTs syntax lets us specify that the TextField
constructor can only be used to construct a Form Text
, not any arbitrary
Form a
.
The second two constructors (TextField
and Checkbox
) are easy – they let
us create labelled inputs. (In digestive-functors
they can also contain
values, weirdly. It doesn't make sense to me, because when you're
describing a form it doesn't make sense to also fill it – the values are
supposed to be provided by the user. I have spent some time thinking about
it and I don't see a good reason for this design, so in my toy realization
I'm going to omit this detail.)
The first two constructors are used for sticking together the components of the form. In the next section we'll see how it's done.
We construct forms with <$>
and <*>
, so our Form
must have an
Applicative
instance and a Functor
instance. The Pure
and Ap
constructors are exactly what we need to write it:
instance Functor Form where
fmap f = Ap (Pure f)
instance Applicative Form where
pure = Pure
(<*>) = Ap
Now we can construct simple forms that become trees of Ap
s:
registerForm =
User <$> TextField "first_name" ""
<*> TextField "last_name" ""
<*> TextField "email" ""
-- is the same as
registerForm =
Ap (Ap (Ap User (TextField "first_name" ""))
(TextField "last_name" ""))
(TextField "email" "")
Thanks to currying, a chain of any length becomes a nested Ap
application.
If some elements were complex forms instead of single fields, it would've
still been a tree of Ap
s, though the structure would've been a bit more
complex.
A tree like that is very easy to render – just walk through it and render
all fields/checkboxes. I'm going to use printf
for simplicity, though in
real life you should use lucid
or something similar for such tasks.
renderForm :: Form a -> String
renderForm f = "<form>" ++ go f ++ "</form>"
where
go (Pure a) = ""
go (Ap a b) = go a ++ go b
go (TextField name) =
printf "<input type=\"text\" name=%s><br>" (show name)
go (Checkbox name) =
printf "<input type="checkbox" name=%s><br>" (show name)
If you have key–value associations from a POST query, you can also easily evaluate a form:
evalForm :: Map Name Text -> Form a -> a
evalForm kv = go
where
go (Pure a) = a
go (Ap a b) = (go a) $ (go b)
go (TextField name) =
fromMaybe "" (M.lookup name kv)
go (Checkbox name) =
M.lookup name kv == Just "on"
For simplicity I'm not going to add any kind of error handling, validation, etc. We could easily add validation by introducing another constructor:
data Form a where
...
Validate :: (b -> Either Text a) -> Form b -> Form a
This is similar to what digestive-functors
does.
Now that you (maybe) understand the idea behind digestive-functors
, let's
see how to use the actual library. There are three main types:
-
type Form v m a
– a form that can be rendered or evaluated.-
v
is the type for rendered things – e.g.Text
,String
,Html
, or your own custom type. It's used for validation errors, for combobox items, etc -
m
is the monad in which validation happens – can beIdentity
if all your validation is pure, can be somethingIO
-like if you want to e.g. access a DB during validation) -
a
is the type that will be returned during form evaluation – in many cases it's going to be something that can be trivially constructed from the fields contained in the form
-
-
type Formlet v m a = Maybe a -> Form v m a
– simply a function which can be passedNothing
if you want to get a form, orJust
if you want to convert a value into form fields (i.e. do the opposite thing to evaluating a form). It is most commonly used to set default values for form fields. As far as I understand, you're not really supposed to createFormlet
s of your own. Basic primitives provided bydigestive-functors
are all eitherFormlet
s or something close in shape to them. -
View v
is a form that you are supposed to render after thePOST
query if something went wrong. It consists of aForm v m a
, user's input from the previous time they tried to submit the form, and validation errors (that should be displayed to the user when you re-render the form).
Here are some examples of simple forms (which can be combined with <$>
and
<*>
, and have names attached to them with .:
):
text Nothing
stringRead "Expected an int" Nothing
choice [(1, "Apple"), (2, "Pear")] (Just 2) -- pears are the default
-- because they are sweeter <3
If you simply want to apply a function to form's output, you can use <$>
:
reverse <$> text Nothing
You can also use check(M)
to do validation, and validate(M)
to do
transformations that can fail.
Once you have a form, you need to convert it into a View
and then render
it. digestive-functors
doesn't do any rendering for you, but it provides
two helper functions in Text.Digestive.View
:
-
getForm
converts a form into aView
without any input or error message -
postForm
accepts a form and a function for getting form fields from the request (of typePath -> m [FormInput]
), fills the form, and gives you aView
with input and error messages and the result value of the form (if it was evaluated successfully)
You are supposed to render the View
by yourself – the tutorial provides an
adequate example of doing that. Also, you don't actually have to use
getForm
and postForm
– the Spock-digestive
package by the author
of Spock abstracts that away. Here's an example:
loginAction :: SpockAction conn Session st ()
loginAction = do
let formView = F.renderForm loginFormSpec
f <- F.runForm "loginForm" loginForm
case f of
(view, Nothing) ->
site $ formView view
(view, Just loginReq) ->
if lrUser loginReq == "admin" && lrPassword loginReq == "admin1"
then do
sessionRegenerateId
writeSession (Just $ lrUser loginReq)
redirect "/member-area"
else site $ do
H.alertBox H.BootAlertDanger "Sorry, login failed. Try again."
formView view
runForm
automatically checks whether it was a GET or POST request (and
parses the request and fills the form if it was a POST).