Forms 0.9

August 31, 2011

GravatarBy Michael Snoyman

Forms

I've mentioned the boundary issue already: whenever data enters or leaves an application, we need to validate our data. Probably the most difficult place this occurs is forms. Coding forms is complex; in an ideal world, we'd like a solution that addresses the following problems:

  • Ensure data is valid.
  • Marshal string data in the form submission to Haskell datatypes.
  • Generate HTML code for displaying the form.
  • Generate Javascript to do clientside validation and provide more user-friendly widgets, such as date pickers.
  • Build up more complex forms by combining together simpler forms.
  • Automatically assign names to our fields that are guaranteed to be unique.

The yesod-form package provides all these features in a simple, declarative API. It builds on top of Yesod's widgets to simplify styling of forms and applying Javascript appropriately. And like the rest of Yesod, it uses Haskell's type system to make sure everything is working correctly.

Synopsis

{-# LANGUAGE QuasiQuotes, TemplateHaskell, MultiParamTypeClasses,
OverloadedStrings, TypeFamilies #-}
import Yesod
import Yesod.Form.Jquery
import Data.Time (Day)
import Data.Text (Text)
import Control.Applicative ((<$>), (<*>))

data Synopsis = Synopsis

mkYesod "Synopsis" [parseRoutes|
/ RootR GET
/person PersonR POST
|]

instance Yesod Synopsis where
    approot _ = ""

-- Tells our application to use the standard English messages.
-- If you want i18n, then you can supply a translating function instead.
instance RenderMessage Synopsis FormMessage where
    renderMessage _ _ = defaultFormMessage

-- And tell us where to find the jQuery libraries. We'll just use the defaults,
-- which point to the Google CDN.
instance YesodJquery Synopsis

-- The datatype we wish to receive from the form
data Person = Person
    { personName :: Text
    , personBirthday :: Day
    , personFavoriteColor :: Maybe Text
    , personEmail :: Text
    , personWebsite :: Maybe Text
    }
  deriving Show

-- Declare the form. The type signature is a bit intimidating, but here's the
-- overview:
--
-- * The Html parameter is used for encoding some extra information, such as a
-- nonce for avoiding CSRF attacks
--
-- * We have the sub and master site types, as usual.
--
-- * FormResult can be in three states: FormMissing (not data available),
-- FormFailure (invalid data) and FormSuccess
--
-- * The Widget is the viewable form to place into the web page.
personForm :: Html -> Form Synopsis Synopsis (FormResult Person, Widget)
personForm = renderDivs $ Person
    <$> areq textField "Name" Nothing
    <*> areq (jqueryDayField def
        { jdsChangeYear = True -- give a year dropdown
        , jdsYearRange = "1900:-5" -- 1900 till five years ago
        }) "Birthday" Nothing
    <*> aopt textField "Favorite color" Nothing
    <*> areq emailField "Email address" Nothing
    <*> aopt urlField "Website" Nothing

-- The GET handler displays the form
getRootR :: Handler RepHtml
getRootR = do
    -- Generate the form to be displayed
    ((_, widget), enctype) <- generateFormPost personForm
    defaultLayout [whamlet|
<p>The widget generated contains only the contents of the form, not the form tag itself. So...
<form method=post action=@{PersonR} enctype=#{enctype}>
    ^{widget}
    <p>It also doesn't include the submit button.
    <input type=submit>
|]

-- The POST handler processes the form. If it is successful, it displays the
-- parsed person. Otherwise, it displays the form again with error messages.
postPersonR :: Handler RepHtml
postPersonR = do
    ((result, widget), enctype) <- runFormPost personForm
    case result of
        FormSuccess person -> defaultLayout [whamlet|<p>#{show person}|]
        _ -> defaultLayout [whamlet|
<p>Invalid input, let's try again.
<form method=post action=@{PersonR} enctype=#{enctype}>
    ^{widget}
    <input type=submit>
|]

main :: IO ()
main = warpDebug 3000 Synopsis

Kinds of Forms

Before jumping into the types themselves, we should begin with an overview of the different kinds of forms. There are three categories:

Applicative
These are the most commonly used (it's what appeared in the synopsis). Applicative gives us some nice properties of letting error messages coallesce together and keep a very high-level, declarative approach.
Monadic
A more powerful alternative to applicative. While this allows you more flexibility, at the cost of being more verbose. Useful if you want to create forms that don't fit into the standard two-column look.
Input
Used only for receiving input. Does not generate any HTML for receiving the user input. Useful for interacting with existing forms.

In addition, there are a number of different variables that come into play for each form and field you will want to set up:

  • Is the field required or optional?
  • Should it be submitted with GET or POST?
  • Does it have a default value, or not?

An overriding goal is to minimize the number of field definitions and let them work in as many contexts as possible. One result of this is that we end up with a few extra words for each field. In the synopsis, you may have noticed things like areq and that extra Nothing parameter. We'll cover why all of those exist in the course of this chapter, but for now realize that by making these parameters explicit, we are able to reuse the individuals fields (like intField) in many different ways.

Types

The Yesod.Form.Types module declares a few types. Let's start off with some simple helpers:

Enctype
The encoding type, either UrlEncoded or Multipart. This datatype declares an instance of ToHtml, so you can use the enctype directly in Hamlet.
Env
Maps a parameter name to a list of values.
FileEnv
Maps a parameter name to the associated uploaded file.
Ints
As mentioned in the introduction, yesod-form automatically assigns a unique name to each field. Ints is used to keep track of the next number to assign.
FormResult
Has one of three possible states: FormMissing if no data was submitted, FormFailure if there was an error parsing the form (e.g., missing a required field, invalid content), or FormSuccess if everything went smoothly.

Next we have three datatypes used for defining individual fields.

Field
Defines two pieces of functionality: how to parse the text input from a user into a Haskell value, and how to create the widget to be displayed to the user. yesod-form defines a number of individual Fields in Yesod.Form.Fields.
FieldSettings
Basic information on how a field should be displayed, such as the display name, an optional tooltip, and possibly hardcoded id and name attributes. (If none are provided, they are automatically generated.)
FieldView
An intermediate format containing a bunch of view information on a field. This is hardly ever used directly by the user, we'll see more details later.

And finally, we get to the important stuff: the forms themselves. There are three types for this: Form is for monadic forms, AForm for Applicative and IForm (declared in IForm) for input. Form is actually just a simple type synonym for a monad stack that provides the following features:

  • A Reader monad giving us the parameters (Env and FileEnv), the master site argument and the list of languages the user supports. The last two are used for i18n (more on this later).
  • A Writer monad keeping track of the Enctype. A form will always be UrlEncoded, unless there is a file input field, which will force us to use multipart instead.
  • A State monad holding an Ints to keep track of the next unique name to produce.

An AForm is pretty similar. However, there are a few major differences:

  • It produces a list of FieldViews. This allows us to keep an abstract idea of the form display, and then at the end of the day choose an appropriate function for laying it out on the page. In the synopsis, we used renderDivs, which creates a bunch of div tags. Another options would be renderTable.
  • It does not provide a Monad instance. The goal of Applicative is to allow the entire form to run, grab as much information on each field as possible, and then create the final result. This cannot work in the context of Monad.

An IForm is even simpler: it returns either a list of error messages or a result.

Converting

"But wait a minute," you say. "You said the synopsis uses applicative forms, but I'm sure the type signature said Form. Shouldn't it be Monadic?" That's true, the final form we produced was monadic. But what really happened is that we converted an applicative form to a monadic one.

Again, our goal is to reuse code as much as possible, and minimize the number of functions in the API. And Monadic forms are more powerful than Applicative, if more clumsy, so anything that can be expressed in an Applicative form could also be expressed in a Monadic form. There are two core functions that help out with this: aformToForm converts any applicative form to a monadic one, and formToAForm converts certain kinds of monadic forms to applicative forms.

"But wait another minute," you insist. "I didn't see any aformToForm!" Also true. The renderDivs function takes care of that for us.

Create AForms

Now that I've (hopefully) convinced you that in our synopsis we were really dealing with applicative forms, let's have a look and try to understand how these things get created. Let's take a simple example:

data Car = Car
    { carModel :: Text
    , carYear :: Int
    }
  deriving Show

carAForm :: AForm Synopsis Synopsis Car
carAForm = Car
    <$> areq textField "Model" Nothing
    <*> areq intField "Year" Nothing

carForm :: Html -> Form Synopsis Synopsis (FormResult Car, Widget)
carForm = renderTable carAForm

Here, we've explicitly split up applicative and monadic forms. In carAForm, we use the <$> and <*> operators. This should be surprising; these are almost always used in applicative-style code. (For more information on applicative code, see the Haskell wiki.) And we have one line for each record in our Car datatype. Perhaps unsurprisingly, we have a textField for the Text record, and an intField for the Int record.

Let's look a bit more closely at the areq function. Its (simplified) type signature is Field a -> FieldSettings -> Maybe a -> AForm a. So that first argument is going to determine the datatype of this field, how to parse it, and how to render it. The next argument, FieldSettings, tells us the label, tooltip, name and ID of the field. In this case, we're using the previously-mentioned IsString instance of FieldSettings.

And what's up with that Maybe a? It provides the optional default value. So let's say we want our form to fill in "2007" as the default car year, we would use areq intField "Year" (Just 2007). We can even take this to the next level, and have a form that takes an optional parameter giving the default values.

Form with default values
carAForm :: Maybe Car -> AForm Synopsis Synopsis Car
carAForm mcar = Car
    <$> areq textField "Model" (carModel <$> mcar)
    <*> areq intField "Year" (carYear <$> mcar)

Optional fields

Now let's say that we wanted to have an optional field (like the car color). All we do instead is use the aopt function.

Optional fields
data Car = Car
    { carModel :: Text
    , carYear :: Int
    , carColor :: Maybe Text
    }
  deriving Show

carAForm :: AForm Synopsis Synopsis Car
carAForm = Car
    <$> areq textField "Model" Nothing
    <*> areq intField "Year" Nothing
    <*> aopt textField "Color" Nothing

And like required fields, the last argument is the optional default value. However, this has two layers of Maybe wrapping. This may seem redundant (and it is), but it makes it much easier to write code that takes an optional default form parameter.

Default optional fields
data Car = Car
    { carModel :: Text
    , carYear :: Int
    , carColor :: Maybe Text
    }
  deriving Show

carAForm :: Maybe Car -> AForm Synopsis Synopsis Car
carAForm mcar = Car
    <$> areq textField "Model" (carModel <$> mcar)
    <*> areq intField "Year" (carYear <$> mcar)
    <*> aopt textField "Color" (carColor <$> mcar)

carForm :: Html -> Form Synopsis Synopsis (FormResult Car, Widget)
carForm = renderTable $ carAForm $ Just $ Car "Forte" 2010 $ Just "gray"

Validation

Let's say we only want to accept cars created after 1990. How would we go about limiting things? If you remember, we said above that the Field itself contained the information on what is a valid entry. So all we need to do is write a new Field, right? Well, that would be a bit tedious. Instead, let's just modify an existing one:

carAForm :: Maybe Car -> AForm Synopsis Synopsis Car
carAForm mcar = Car
    <$> areq textField "Model" (carModel <$> mcar)
    <*> areq carYearField "Year" (carYear <$> mcar)
    <*> aopt textField "Color" (carColor <$> mcar)
  where
    errorMessage :: Text
    errorMessage = "Your car is too old, get a new one!"

    carYearField = check validateYear intField

    validateYear y
        | y < 1990 = Left errorMessage
        | otherwise = Right y

The trick here is the check function. It takes a function (validateYear) that returns either an error message or a modified field value. In this example, we haven't modified the value at all. That is usually going to be the case. Of course, this kind of checking is very common, so we have a shortcut:

carYearField = checkBool (>= 1990) errorMessage intField

checkBool takes two parameters: a condition that must be fulfilled, and an error message to be displayed if it was not.

This is great to make sure the car isn't too old. But what if we want to make sure that the year specified is not from the future? In order to look up the year, we'll need to run some IO. For such circumstances, we'll need checkM:

carYearField = checkM inPast $ checkBool (>= 1990) errorMessage intField

    inPast y = do
        thisYear <- liftIO getCurrentYear
        return $ if y <= thisYear
            then Right y
            else Left ("You have a time machine!" :: Text)

getCurrentYear :: IO Int
getCurrentYear = do
    now <- getCurrentTime
    let today = utctDay now
    let (year, _, _) = toGregorian today
    return $ fromInteger year

inPast is a simple function that will return an Either result. However, it uses a Handler monad. We use liftIO getCurrentYear to get the current year and then compare it against the user-supplied year. Also, notice how we can easily chain together multiple validators.

More sophiticated fields

Our color entry field is nice, but it's not exactly user-friendly. What we really want is a dropdown list.

Drop-down lists
data Car = Car
    { carModel :: Text
    , carYear :: Int
    , carColor :: Maybe Color
    }
  deriving Show

data Color = Red | Blue | Gray | Black
    deriving (Show, Eq, Enum, Bounded)

carAForm :: Maybe Car -> AForm Synopsis Synopsis Car
carAForm mcar = Car
    <$> areq textField "Model" (carModel <$> mcar)
    <*> areq carYearField "Year" (carYear <$> mcar)
    <*> aopt (selectField colors) "Color" (carColor <$> mcar)
  where
    colors = [("Red", Red), ("Blue", Blue), ("Gray", Gray), ("Black", Black)]

selectField takes a list of pairs. The first item in the pair is the text displayed to the user in the drop-down list, and the second item is the actual Haskell value. Of course, the code above looks really repetitive; we can get the same result using the Enum and Bounded instance GHC automatically derives for us.

Uses Enum and Bounded
data Car = Car
    { carModel :: Text
    , carYear :: Int
    , carColor :: Maybe Color
    }
  deriving Show

data Color = Red | Blue | Gray | Black
    deriving (Show, Eq, Enum, Bounded)

carAForm :: Maybe Car -> AForm Synopsis Synopsis Car
carAForm mcar = Car
    <$> areq textField "Model" (carModel <$> mcar)
    <*> areq carYearField "Year" (carYear <$> mcar)
    <*> aopt (selectField colors) "Color" (carColor <$> mcar)
  where
    colors = map (pack . show &&& id) $ [minBound..maxBound]

[minBound..maxBound] gives us a list of all the different Color values. We then apply a map and &&& to turn that into a list of pairs.

Of course, some people prefer radio buttons to drop-down lists. Fortunately, this is just a one-word change.

Radio buttons
data Car = Car
    { carModel :: Text
    , carYear :: Int
    , carColor :: Maybe Color
    }
  deriving Show

data Color = Red | Blue | Gray | Black
    deriving (Show, Eq, Enum, Bounded)

carAForm :: Maybe Car -> AForm Synopsis Synopsis Car
carAForm mcar = Car
    <$> areq textField "Model" (carModel <$> mcar)
    <*> areq carYearField "Year" (carYear <$> mcar)
    <*> aopt (radioField colors) "Color" (carColor <$> mcar)
  where
    colors = map (pack . show &&& id) $ [minBound..maxBound]

Running forms

At some point, we're going to need to take our beautiful forms and produce some results. There are a number of different functions available for this, each with its own purpose. I'll go through them, starting with the most common.

runFormPost
This will run your form against any submitted POST parameter. If this is not a POST submission, it will return a FormMissing. This automatically inserts a nonce as a hidden form field to avoid CSRF attacks.
runFormGet
Same as runFormPost, for GET submissions. In order to distinguish a normal GET page load from a GET submission, it includes an extra _hasdata hidden field in the form.
runFormPostNoNonce
Same as runFormPost, but does not include (or require) the CSRF nonce.
generateFormPost
Instead of binding to existing POST parameters, acts as if there are none. This can be useful when you want to generate a new form after a previous form was submitted, such as in a wizard.
generateFormGet
Same as generateFormPost, but for GET.

The return type from the first three is ((FormResult a, Widget), Enctype). The Widget will already have any valdiation errors and previously submitted values.

i18n

There have been a few references to i18n in this chapter. The topic will get more thorough coverage in its own chapter, but since it has such a profound effect on yesod-form, I wanted to give a brief overview. The idea behind i18n in Yesod is to have data types represent messages. Each site can have an instance of RenderMessage for a given datatype which will translate that message based on a list of languages the user accepts. As a result of all this, there are a few things you should be aware of:

  • There is an automatic instance of RenderMessage for Text in every site, so you can just use plain strings if you don't care about i18n support. However, you may need to use explicit type signatures occasionally.
  • yesod-form expresses all of its messages in terms of the FormMessage datatype. Therefore, to use yesod-form, you'll need to have an appropriate RenderMessage instance. A simple one that uses the default English translations would be:
    instance RenderMessage MyApp FormMessage where
        renderMessage _ _ = defaultFormMessage
    
    This is provided automatically by the scaffolded site.
  • In order to allow multiple different message types to co-exist, we use an existential type called SomeMessage. You will occasionally need to wrap your values inside of it, though this is not common in normal library use.

TODO

This chapter still needs a bit more work. In particular, it should cover:

  • Monadic forms
  • Input forms
  • Creating new fields

If you can think of anything else it's missing, please leave a comment.

Comments

comments powered by Disqus

Archives