forma-1.1.1: Parse and validate forms in JSON format

Copyright© 2017–2019 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 guards against 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.
  • Perform validation using several form fields at once. You choose which “sub-region” of your form a given check will have access to, see withCheck.

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

Note: version 1.0.0 is completely different from older versions.

Synopsis

Constructing a form

field Source #

Arguments

:: forall (names :: [Symbol]). (Monad m, FromJSON s) 
=> FieldName names

Name of the field

-> (s -> ExceptT e m a)

Checker that performs validation and possibly transformation of the field value

-> FormParser names e 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 Text 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 easily 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 as a value of e type.

To run a form composed from fields, see runForm.

field fieldName check = withCheck fieldName check (field' fieldName)

field' Source #

Arguments

:: forall (names :: [Symbol]). (Monad m, FromJSON a) 
=> FieldName names

Name of the field

-> FormParser names e m a 

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

field' fieldName = subParser fieldName value

value :: (Monad m, FromJSON a) => FormParser names e m a Source #

Interpret the current field as a value of type a.

subParser Source #

Arguments

:: forall (names :: [Symbol]). Monad m 
=> FieldName names

Field name to descend to

-> FormParser names e m a

Subparser

-> FormParser names e m a

Wrapped parser

Use a given parser to parse a field. Suppose that you have a parser loginForm that parses a structure like this one:

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

Then subParser #login loginForm will parse this:

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

withCheck Source #

Arguments

:: forall (names :: [Symbol]). Monad m 
=> FieldName names

Field to assign validation error to

-> (s -> ExceptT e m a)

The check to perform

-> FormParser names e m s

Original parser

-> FormParser names e 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!"

passwordForm =
  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. The field name should be relative and point to a field in the argument parser, not full path from top-level of the form. For example this form:

biggerForm = subParser #password_form passwordForm

will report validation error for the field "password_form.password_confirmation" if the check fails (note that "password_form" is correctly prepended to the field path).

Running a form/inspecting result

runForm Source #

Arguments

:: Monad m 
=> FormParser names e m a

The form parser to run

-> Value

Input for the parser

-> m (FormResult names e a)

The result of parsing

Run a parser on given input.

runFormPure Source #

Arguments

:: FormParser names e Identity a

The form parser to run

-> Value

Input for the parser

-> FormResult names e a

The result of parsing

Run form purely.

Since: 1.1.0

unFieldName :: FieldName names -> NonEmpty Text Source #

Project field path from a FieldName.

showFieldName :: FieldName names -> Text Source #

Project textual representation of path to a field.

Types and type functions

data FormParser (names :: [Symbol]) e 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 and its friends, see below. Users can combine existing parsers using applicative notation.

FormParser is parametrized by four type variables:

  • names—collection of field names we can use in a form to be parsed with this parser.
  • e—type of validation errors.
  • 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 e m) Source # 
Instance details

Defined in Web.Forma

Methods

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

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

Applicative m => Applicative (FormParser names e m) Source # 
Instance details

Defined in Web.Forma

Methods

pure :: a -> FormParser names e m a #

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

liftA2 :: (a -> b -> c) -> FormParser names e m a -> FormParser names e m b -> FormParser names e m c #

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

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

Applicative m => Alternative (FormParser names e m) Source # 
Instance details

Defined in Web.Forma

Methods

empty :: FormParser names e m a #

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

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

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

data FormResult (names :: [Symbol]) e a Source #

Result of parsing. names is the collection of allowed field names, e is the type of validation errors, and a is the type of parsing result.

Constructors

ParsingFailed (Maybe (FieldName names)) Text

Parsing of JSON failed, this is fatal, we shut down and report the parsing error. The first component specifies path to a problematic field and the second component is the text of error message.

ValidationFailed (Map (FieldName names) e)

Validation of a field failed. This is also fatal but we still try to validate other branches (fields) to collect as many validation errors as possible.

Succeeded a

Success, we've got a result to return.

Instances
Functor (FormResult names e) Source # 
Instance details

Defined in Web.Forma

Methods

fmap :: (a -> b) -> FormResult names e a -> FormResult names e b #

(<$) :: a -> FormResult names e b -> FormResult names e a #

Applicative (FormResult names e) Source # 
Instance details

Defined in Web.Forma

Methods

pure :: a -> FormResult names e a #

(<*>) :: FormResult names e (a -> b) -> FormResult names e a -> FormResult names e b #

liftA2 :: (a -> b -> c) -> FormResult names e a -> FormResult names e b -> FormResult names e c #

(*>) :: FormResult names e a -> FormResult names e b -> FormResult names e b #

(<*) :: FormResult names e a -> FormResult names e b -> FormResult names e a #

(Eq e, Eq a) => Eq (FormResult names e a) Source # 
Instance details

Defined in Web.Forma

Methods

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

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

(Show e, Show a) => Show (FormResult names e a) Source # 
Instance details

Defined in Web.Forma

Methods

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

show :: FormResult names e a -> String #

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

(ToJSON e, ToJSON a) => ToJSON (FormResult names e a) Source # 
Instance details

Defined in Web.Forma

Methods

toJSON :: FormResult names e a -> Value #

toEncoding :: FormResult names e a -> Encoding #

toJSONList :: [FormResult names e a] -> Value #

toEncodingList :: [FormResult names e a] -> Encoding #

data FieldName (names :: [Symbol]) Source #

FieldName names represents a non-empty vector of ErrorMessage components that serve as a path to some field in a JSON structure. Every component 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 the type FieldName is by using OverloadedLabels. Note that you can combine field names using (<>).

showFieldName (#login_form <> #username) = "login_form.username"
Instances
(KnownSymbol name, InSet name names) => IsLabel name (FieldName names) Source # 
Instance details

Defined in Web.Forma

Methods

fromLabel :: FieldName names #

Eq (FieldName names) Source # 
Instance details

Defined in Web.Forma

Methods

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

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

Ord (FieldName names) Source # 
Instance details

Defined in Web.Forma

Methods

compare :: FieldName names -> FieldName names -> Ordering #

(<) :: FieldName names -> FieldName names -> Bool #

(<=) :: FieldName names -> FieldName names -> Bool #

(>) :: FieldName names -> FieldName names -> Bool #

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

max :: FieldName names -> FieldName names -> FieldName names #

min :: FieldName names -> FieldName names -> FieldName names #

Show (FieldName names) Source # 
Instance details

Defined in Web.Forma

Methods

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

show :: FieldName names -> String #

showList :: [FieldName names] -> ShowS #

Semigroup (FieldName names) Source # 
Instance details

Defined in Web.Forma

Methods

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

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

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

ToJSON (FieldName names) Source # 
Instance details

Defined in Web.Forma

Methods

toJSON :: FieldName names -> Value #

toEncoding :: FieldName names -> Encoding #

toJSONList :: [FieldName names] -> Value #

toEncodingList :: [FieldName names] -> Encoding #

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