forma-0.2.0: Parse and validate forms in JSON format

Copyright© 2017 Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Web.Forma

Contents

Description

This module provides a tool for validation of forms that are represented in the JSON format. Sending forms in JSON format via an AJAX request instead of traditional submitting of forms has a number of advantages:

  • Smoother user experience: no need to reload the whole page.
  • Form rendering is separated and lives only in GET handler, POST (or whatever method you deem appropriate for your use case) handler only handles validation and actual effects that form submission should initiate.
  • You get a chance to organize form input just like you want.

The task of validation of a form in the JSON format may seem simple, but it's not trivial to get it right. The library allows you to:

  • Define form parser using type-safe applicative notation with field labels being stored on the type label which excludes any possibility of typos and will force all your field labels be always up to date.
  • Parse JSON Value according to the definition of form you created.
  • Stop parsing immediately if given form is malformed and cannot be processed.
  • Validate forms using any number of composable checkers that you write for your specific problem domain. Once you have a vocabulary of checkers, creation of new forms is just a matter of combining them, and yes they do combine nicely.
  • Collect validation errors from multiple branches of parsing (one branch per form field) in parallel, so validation errors in one branch do not prevent us from collecting validation errors from other branches. This allows for a better user experience as the user can see all validation errors at the same time.
  • Use optional and (<|>) from Control.Applicative in your form definitions instead of ugly ad-hoc stuff (yes digestive-functors, I'm looking at you).
  • When individual validation of fields is done, you get a chance to perform some actions and either decide that form submission has succeeded, or indeed perform additional checks that may depend on several form fields at once and signal a validation error assigned to a specific field(s). This constitute the “second level” of validation, so to speak.

This library requires at least GHC 8 to work.

You need to enable at least DataKinds and TypeApplications language extensions to use this library.

Synopsis

Constructing a form

field Source #

Arguments

:: forall (name :: Symbol) (names :: [Symbol]). (KnownSymbol name, InSet name names, Monad m, ToJSON e, FromJSON s) 
=> (s -> ExceptT e m a)

Checker that performs validation and possibly transformation of the field value

-> FormParser names m a 

Construct a parser for a field. Combine multiple fields using applicative syntax like so:

type LoginFields = '["username", "password", "remember_me"]

data LoginForm = LoginForm
  { loginUsername   :: Text
  , loginPassword   :: Text
  , loginRememberMe :: Bool
  }

loginForm :: Monad m => FormParser LoginFields m LoginForm
loginForm = LoginForm
  <$> field @"username" notEmpty
  <*> field @"password" notEmpty
  <*> field' @"remember_me"

notEmpty :: Monad m => Text -> ExceptT Text m Text
notEmpty txt =
  if T.null txt
    then throwError "This field cannot be empty"
    else return txt

Referring to the types in the function's signature, s is extracted from JSON Value for you automatically using its FromJSON instance. The field value is taken in assumption that top level Value is a dictionary, and field name is a key in that dictionary. So for example a valid JSON input for the form shown above could be this:

{
  "username": "Bob",
  "password": "123",
  "remember_me": true
}

Once value of type s is extracted, validation phase beings. The supplied checker (you can easy compose them with (>=>), as they are Kleisli arrows) is applied to the s value and validation either succeeds producing an a value, or we collect an error in the form of a value of e type, which is fed into mkFieldError internally.

To run a form composed from fields, see runForm.

field' :: forall name names m a. (KnownSymbol name, InSet name names, Monad m, FromJSON a) => FormParser names m a Source #

The same as field, but does not require a checker.

withCheck Source #

Arguments

:: forall (name :: Symbol) (names :: [Symbol]). (KnownSymbol name, InSet name names, Monad m, ToJSON e) 
=> (s -> ExceptT e m a)

The check to perform

-> FormParser names m s

Original parser

-> FormParser names m a

Parser with the check attached

Transform a form by applying a checker on its result.

passwordsMatch (a, b) = do
  if a == b
    then return a
    else throwError "Passwords don't match!"

createNewPasswordForm =
  withCheck @"password_confirmation" passwordsMatch
    ((,) <$> field @"password" notEmpty
         <*> field @"password_confirmation" notEmpty)

Note that you must specify the field name on which to add a validation error message in case the check fails.

Since: 0.2.0

Running a form

runForm Source #

Arguments

:: (Monad m, ToJSON b) 
=> FormParser names m a

The form parser to run

-> Value

Input for the parser

-> (a -> m (FormResult names b))

Callback that is called on success

-> m Value

The result to send back to the client

Run the supplied parser on given input and call the specified callback that uses the result of parsing on success.

The callback can either report a FieldError (one or more), or report success providing a value that will be converted to JSON and included in the resulting Value (response).

The resulting Value has the following format:

{
  "parse_error": "Text or null."
  "field_errors":
    {
      "foo": "Foo's error serialized to JSON.",
      "bar": "Bar's error…"
    }
  "result": "What you return from the callback in FormResultSuccess."
}

pick :: forall name names. (KnownSymbol name, InSet name names) => SelectedName names Source #

Pick a name from a given collection of names.

Typical usage:

type Fields = '["foo", "bar", "baz"]

myName :: SelectedName Fields
myName = pick @"foo" @Fields

It's a good idea to use pick to get field names not only where this approach is imposed by the library, but everywhere you need to use the field names, in your templates for example.

unSelectedName :: SelectedName names -> Text Source #

Extract a Text value from SelectedName.

mkFieldError Source #

Arguments

:: ToJSON e 
=> SelectedName names

The field name

-> e

Data that represents error

-> FieldError names 

This is a smart constructor for the FieldError type, and the only way to obtain values of that type.

Typical usage:

type Fields = '["foo", "bar", "baz"]

myError :: FieldError Fields
myError = mkFieldError (pick @"foo" @Fields) "That's all wrong."

See also: pick (to create SelectedName).

Types and type functions

data FormParser names m a Source #

The type represents the parser that you can run on a Value with the help of runForm. The only way for the user of the library to create a parser is via the field function. Users can combine existing parsers using the applicative notation.

FormParser is parametrized by three type variables:

  • names—collection of field names we can use in a form to be parsed with this parser.
  • m—underlying monad, FormParser is not a monad itself, so it's not a monad transformer, but validation can make use of the m monad.
  • a—result of parsing.

FormParser is not a monad because it's not possible to write a Monad instance with the properties that we want (validation errors should not lead to short-cutting behavior).

Instances

Functor m => Functor (FormParser names m) Source # 

Methods

fmap :: (a -> b) -> FormParser names m a -> FormParser names m b #

(<$) :: a -> FormParser names m b -> FormParser names m a #

Applicative m => Applicative (FormParser names m) Source # 

Methods

pure :: a -> FormParser names m a #

(<*>) :: FormParser names m (a -> b) -> FormParser names m a -> FormParser names m b #

(*>) :: FormParser names m a -> FormParser names m b -> FormParser names m b #

(<*) :: FormParser names m a -> FormParser names m b -> FormParser names m a #

Applicative m => Alternative (FormParser names m) Source # 

Methods

empty :: FormParser names m a #

(<|>) :: FormParser names m a -> FormParser names m a -> FormParser names m a #

some :: FormParser names m a -> FormParser names m [a] #

many :: FormParser names m a -> FormParser names m [a] #

data FormResult names a Source #

This a type that user must return in the callback passed to the runForm function. Quite simply, it allows you either report a error or finish successfully.

Constructors

FormResultError (FieldError names)

Form submission failed, here are the validation errors.

FormResultSuccess a

Form submission succeeded, send this info.

Instances

Eq a => Eq (FormResult names a) Source # 

Methods

(==) :: FormResult names a -> FormResult names a -> Bool #

(/=) :: FormResult names a -> FormResult names a -> Bool #

Show a => Show (FormResult names a) Source # 

Methods

showsPrec :: Int -> FormResult names a -> ShowS #

show :: FormResult names a -> String #

showList :: [FormResult names a] -> ShowS #

data SelectedName names Source #

SelectedName names represents a name (Text value) that is guaranteed to be in the names, which is a set of strings on type level. The purpose if this type is to avoid typos and to force users to update field names everywhere when they decide to change them. The only way to obtain a value of type SelectedName is via the pick function, which see.

Instances

Eq (SelectedName names) Source # 

Methods

(==) :: SelectedName names -> SelectedName names -> Bool #

(/=) :: SelectedName names -> SelectedName names -> Bool #

Show (SelectedName names) Source # 

Methods

showsPrec :: Int -> SelectedName names -> ShowS #

show :: SelectedName names -> String #

showList :: [SelectedName names] -> ShowS #

type family InSet (n :: Symbol) (ns :: [Symbol]) :: Constraint where ... Source #

The type function computes a Constraint which is satisfied when its first argument is contained in its second argument. Otherwise a friendly type error is displayed.

Equations

InSet n '[] = TypeError (((Text "The name " :<>: ShowType n) :<>: Text " is not in the given set.") :$$: Text "Either it's a typo or you need to add it to the set first.") 
InSet n (n ': ns) = () 
InSet n (m ': ns) = InSet n ns 

data FieldError names Source #

Error info in JSON format associated with a particular form field. Parametrized by names, which is a collection of field names (on type level) the target field belongs to. FieldError is an instance of Semigroup and that's how you combine values of that type. Note that it's not a Monoid, because we do not want to allow empty FieldErrors.

Instances

Eq (FieldError names) Source # 

Methods

(==) :: FieldError names -> FieldError names -> Bool #

(/=) :: FieldError names -> FieldError names -> Bool #

Show (FieldError names) Source # 

Methods

showsPrec :: Int -> FieldError names -> ShowS #

show :: FieldError names -> String #

showList :: [FieldError names] -> ShowS #

Semigroup (FieldError names) Source # 

Methods

(<>) :: FieldError names -> FieldError names -> FieldError names #

sconcat :: NonEmpty (FieldError names) -> FieldError names #

stimes :: Integral b => b -> FieldError names -> FieldError names #

ToJSON (FieldError names) Source #