grab-form-0.0.0.8: Applicative parsers for form parameter lists
Safe HaskellNone
LanguageHaskell2010

Data.GrabForm

Synopsis

Tutorial

We are concerned here with data submitted by web browsers in a normal form submission. Ignoring the encoding details, we can think of a form as looking something like this:

name:               Alonzo
state:              Montana
security_question:  What is your favorite hobby?
security_answer:    watching cars

This example has four parameters. Each parameter has a name and a value. We might represent this in Haskell as:

[ ("name", "Alonzo")
, ("state", "Montana")
, ("security_question", "What is your favorite hobby?")
, ("security_answer", "watching cars")
]

Suppose we're only interested in two parts of this form: The name and the state.

nameAndState :: Grab EnglishSentence (Text, Text)
nameAndState =
    (,)
        <$> at "name" (only text)
        <*> at "state" (only text)

If we apply nameAndState to the form parameters above, we get the following result: ("Alonzo", "Montana")

λ> :{
 > readTextParams (etAlia nameAndState)
 >     [ ("name", "Alonzo")
 >     , ("state", "Montana")
 >     , ("security_question", "What is your favorite hobby?")
 >     , ("security_answer", "watching cars")
 >     ]
 > :}
( Log []
, Just ("Alonzo", "Montana")
)

When receiving information submitted from an external source, there is usually some possibility that the input is invalid. Consider the following form that is missing the "state" field. In this case, the result we get is Nothing, accompanied by an error message indicating that something is missing.

λ> :{
 > readTextParams (etAlia nameAndState)
 >     [ ("name", "Alonzo")
 >     , ("security_question", "What is your favorite hobby?")
 >     , ("security_answer", "watching cars")
 >     ]
 > :}
( Log [("state", "Required parameter is missing.")]
, Nothing
)

The etAlia function we've been using signifies that the input is allowed to contain parameters other than the ones that nameAndState grabs. If we use only instead, we can specify that there should be no additional parameters.

λ> :{
 > readTextParams (only nameAndState)
 >     [ ("name", "Alonzo")
 >     , ("state", "Montana")
 >     , ("security_question", "What is your favorite hobby?")
 >     , ("security_answer", "watching cars")
 >     ]
 > :}
( Log [ ("security_question", "Unexpected parameter.")
      , ("security_answer", "Unexpected parameter.")
      ]
, Just ("Alonzo", "Montana")
)

However, we still get the result: ("Alonzo", "Montana"). Unexpected parameters do not prevent us from being able to read the form. Whether you choose only or etAlia only determines whether these warnings end up in the log; it does not affect whether reading the form succeeds or fails.

Duplicate parameters are not permitted, since we cannot know which of the values to accept as the real one. Alonzo cannot live in both Georgia and Montana:

λ> :{
 > readTextParams (only nameAndState)
 >     [ ("name", "Alonzo")
 >     , ("state", "Georgia")
 >     , ("state", "Montana")
 >     ]
 > :}
( Log [("state", "Parameter may not appear more than once.")]
, Nothing
)

Duplicated parameters are only allowed if they have the same value, because in that case the problem of deciding which value to accept does not arise.

λ> :{
 > readTextParams (only nameAndState)
 >     [ ("name", "Alonzo")
 >     , ("state", "Montana")
 >     , ("state", "Montana")
 >     ]
 > :}
( Log []
, Just ("Alonzo", "Montana")
)

Sometimes a form has a tree structure. Suppose there are multiple security questions. If we were using a data format like YAML, it might look like this:

name: Alonzo
state: Montana
security:
  - Q: What is your favorite hobby?
    A: watching cars
  - Q: What is your oldest sibling's name?
    A: melman
  - Q: What was the make and model of your first car?
    A: bmw x5

To cajole this data into our concept of a form as a list of parameters, we need to flatten it somehow. We adopt the following convention:

name:           Alonzo
state:          Montana
security[1].Q:  What is your favorite hobby?
security[1].A:  watching cars
security[2].Q:  What is your oldest sibling's name?
security[2].A:  melman
security[3].Q:  What was the make and model of your first car?
security[3].A:  bmw x5

Let's define a data type to represent a question and answer:

data QA = QA { qa_question :: Text, qa_answer :: Text } deriving (Eq, Show)
nameStateAndQAs :: Grab EnglishSentence (Text, Text, [QA])
nameStateAndQAs =
    (,,)
        <$> at "name" (only text)
        <*> at "state" (only text)
        <*> at "security" (only (natList (only qa)))
qa :: Grab EnglishSentence QA
qa =
    QA
        <$> at "Q" (only text)
        <*> at "A" (only text)
λ> :{
 > readTextParams (only nameStateAndQAs)
 >     [ ("name", "Alonzo")
 >     , ("state", "Montana")
 >     , ("security[0].Q", "What is your favorite hobby?")
 >     , ("security[0].A", "watching cars")
 >     , ("security[1].Q", "What is your oldest sibling's name?")
 >     , ("security[1].A", "melman")
 >     , ("security[2].Q", "What was the make and model of your first car?")
 >     , ("security[2].A", "bmw x5")
 >     ]
 > :}
( Log []
, Just
      ( "Alonzo"
      , "Montana"
      , [ QA
            { qa_question = "What is your favorite hobby?"
            , qa_answer = "watching cars"
            }
        , QA
            { qa_question = "What is your oldest sibling's name?"
            , qa_answer = "melman"
            }
        , QA
            { qa_question = "What was the make and model of your first car?"
            , qa_answer = "bmw x5"
            }
        ]
      )
)

The parameters of the list may appear in any order. The order of the result is determined by the numbers in the parameter names.

λ> :{
 > readTextParams (only (at "security" (only (natList (only qa)))))
 >     [ ("security[2].Q", "What was the make and model of your first car?")
 >     , ("security[1].A", "melman")
 >     , ("security[0].Q", "What is your favorite hobby?")
 >     , ("security[1].Q", "What is your oldest sibling's name?")
 >     , ("security[0].A", "watching cars")
 >     , ("security[2].A", "bmw x5")
 >     ]
 > :}
( Log []
, Just
      [ QA
          { qa_question = "What is your favorite hobby?"
          , qa_answer = "watching cars"
          }
      , QA
          { qa_question = "What is your oldest sibling's name?"
          , qa_answer = "melman"
          }
      , QA
          { qa_question = "What was the make and model of your first car?"
          , qa_answer = "bmw x5"
          }
      ]
)

Error messages work the same within nested grabs. The result is a complete list of every error encountered.

λ> :{
 > readTextParams (only nameStateAndQAs)
 >     [ ("state", "Montana")
 >     , ("itchy face", "yes")
 >     , ("security[0].Q", "What is your favorite hobby?")
 >     , ("security[0].A", "watching cars")
 >     , ("security[1].Q", "What is your oldest sibling's name?")
 >     , ("security[1].A", "melman")
 >     , ("security[1].A", "iowa")
 >     , ("security[2].Q", "What was the make and model of your first car?")
 >     , ("security[2].A", "bmw x5")
 >     , ("security[2].A2", "xyz")
 >     ]
 > :}
( Log [ ("name", "Required parameter is missing.")
      , ("itchy face", "Unexpected parameter.")
      , ("security[1].A", "Parameter may not appear more than once.")
      , ("security[2].A2", "Unexpected parameter.")
      ]
, Nothing
)

What is a form

The Parameter type

data Param Source #

Constructors

Param 

Fields

Instances

Instances details
Eq Param Source # 
Instance details

Defined in Data.GrabForm

Methods

(==) :: Param -> Param -> Bool #

(/=) :: Param -> Param -> Bool #

Ord Param Source # 
Instance details

Defined in Data.GrabForm

Methods

compare :: Param -> Param -> Ordering #

(<) :: Param -> Param -> Bool #

(<=) :: Param -> Param -> Bool #

(>) :: Param -> Param -> Bool #

(>=) :: Param -> Param -> Bool #

max :: Param -> Param -> Param #

min :: Param -> Param -> Param #

Show Param Source # 
Instance details

Defined in Data.GrabForm

Methods

showsPrec :: Int -> Param -> ShowS #

show :: Param -> String #

showList :: [Param] -> ShowS #

The Name type

newtype Name Source #

Constructors

Name [NamePart] 

Instances

Instances details
Eq Name Source # 
Instance details

Defined in Data.GrabForm

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 
Instance details

Defined in Data.GrabForm

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in Data.GrabForm

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name Source # 
Instance details

Defined in Data.GrabForm

Methods

fromString :: String -> Name #

data NamePart Source #

Instances

Instances details
Eq NamePart Source # 
Instance details

Defined in Data.GrabForm

Ord NamePart Source # 
Instance details

Defined in Data.GrabForm

Show NamePart Source # 
Instance details

Defined in Data.GrabForm

IsString NamePart Source # 
Instance details

Defined in Data.GrabForm

The Form type

data Form Source #

Constructors

Form 

Fields

Error messages

The Log type

newtype Log err Source #

Constructors

Log (Set (Name, err)) 

Instances

Instances details
Eq err => Eq (Log err) Source # 
Instance details

Defined in Data.GrabForm

Methods

(==) :: Log err -> Log err -> Bool #

(/=) :: Log err -> Log err -> Bool #

Show err => Show (Log err) Source # 
Instance details

Defined in Data.GrabForm

Methods

showsPrec :: Int -> Log err -> ShowS #

show :: Log err -> String #

showList :: [Log err] -> ShowS #

Ord err => Semigroup (Log err) Source # 
Instance details

Defined in Data.GrabForm

Methods

(<>) :: Log err -> Log err -> Log err #

sconcat :: NonEmpty (Log err) -> Log err #

stimes :: Integral b => b -> Log err -> Log err #

Ord err => Monoid (Log err) Source # 
Instance details

Defined in Data.GrabForm

Methods

mempty :: Log err #

mappend :: Log err -> Log err -> Log err #

mconcat :: [Log err] -> Log err #

Error classes

class Err_Missing a where Source #

Methods

err_missing :: a Source #

A parameter was expected, but none was given.

Instances

Instances details
Err_Missing () Source # 
Instance details

Defined in Data.GrabForm

Methods

err_missing :: () Source #

Err_Missing EnglishSentence Source # 
Instance details

Defined in Data.GrabForm

class Err_Duplicate a where Source #

Methods

err_duplicate :: a Source #

A parameter was given repeatedly in a situation where it was expected to be present at most once.

Instances

Instances details
Err_Duplicate () Source # 
Instance details

Defined in Data.GrabForm

Methods

err_duplicate :: () Source #

Err_Duplicate EnglishSentence Source # 
Instance details

Defined in Data.GrabForm

class Err_Unexpected a where Source #

Methods

err_unexpected :: a Source #

An unexpected parameter was given.

Instances

Instances details
Err_Unexpected () Source # 
Instance details

Defined in Data.GrabForm

Methods

err_unexpected :: () Source #

Err_Unexpected EnglishSentence Source # 
Instance details

Defined in Data.GrabForm

class Err_OnlyAllowed a where Source #

Methods

err_onlyAllowed Source #

Arguments

:: Text

The allowed value

-> a 

There is only one allowed value for a parameter, and something different was given.

Instances

Instances details
Err_OnlyAllowed () Source # 
Instance details

Defined in Data.GrabForm

Methods

err_onlyAllowed :: Text -> () Source #

Err_OnlyAllowed EnglishSentence Source # 
Instance details

Defined in Data.GrabForm

English sentences as error messages

newtype EnglishSentence Source #

Constructors

EnglishSentence Text 

Instances

Instances details
Eq EnglishSentence Source # 
Instance details

Defined in Data.GrabForm

Ord EnglishSentence Source # 
Instance details

Defined in Data.GrabForm

Show EnglishSentence Source # 
Instance details

Defined in Data.GrabForm

IsString EnglishSentence Source # 
Instance details

Defined in Data.GrabForm

Err_OnlyAllowed EnglishSentence Source # 
Instance details

Defined in Data.GrabForm

Err_Unexpected EnglishSentence Source # 
Instance details

Defined in Data.GrabForm

Err_Duplicate EnglishSentence Source # 
Instance details

Defined in Data.GrabForm

Err_Missing EnglishSentence Source # 
Instance details

Defined in Data.GrabForm

Grabbing data from forms

Types: Grab and Dump

type Grab err a = Simple Form (Log err) a Source #

type Dump err a = Dump Form (Log err) a Source #

Parameter name selection

at :: Ord err => NamePart -> Dump err a -> Grab err a Source #

Simple form fields

text :: forall err. (Ord err, Err_Missing err, Err_Duplicate err) => Grab err Text Source #

optionalText :: forall err. (Ord err, Err_Duplicate err) => Grab err (Maybe Text) Source #

checkbox :: forall err. (Ord err, Err_OnlyAllowed err) => Text -> Grab err Bool Source #

Lists

natList :: Ord err => Dump err a -> Grab err [a] Source #

natListWithIndex :: forall err a. Ord err => Dump err a -> Grab err [(Natural, a)] Source #

Dealing with unrecognized parameters

only :: forall err a. (Ord err, Err_Unexpected err) => Grab err a -> Dump err a Source #

etAlia :: Grab err a -> Dump err a Source #

remainder :: Ord err => Grab err [Param] Source #

Applying a grab to a form

readTextParams :: Ord err => Dump err a -> [(Text, Text)] -> (Log err, Maybe a) Source #