| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Web.Internal.FormUrlEncoded
- class ToFormKey k where
- class FromFormKey k where
- newtype Form = Form {}
- class ToForm a where
- fromEntriesByKey :: (ToFormKey k, ToHttpApiData v) => [(k, [v])] -> Form
- data Proxy3 a b c = Proxy3
- type family NotSupported (cls :: k1) (a :: k2) (reason :: Symbol) :: Constraint where ...
- genericToForm :: forall a. (Generic a, GToForm a (Rep a)) => FormOptions -> a -> Form
- class GToForm t (f :: * -> *) where
- class FromForm a where
- toEntriesByKey :: (FromFormKey k, FromHttpApiData v) => Form -> Either Text [(k, [v])]
- genericFromForm :: forall a. (Generic a, GFromForm a (Rep a)) => FormOptions -> Form -> Either Text a
- class GFromForm t (f :: * -> *) where
- urlEncodeForm :: Form -> ByteString
- urlDecodeForm :: ByteString -> Either Text Form
- urlDecodeAsForm :: FromForm a => ByteString -> Either Text a
- urlEncodeAsForm :: ToForm a => a -> ByteString
- lookupAll :: Text -> Form -> [Text]
- lookupMaybe :: Text -> Form -> Either Text (Maybe Text)
- lookupUnique :: Text -> Form -> Either Text Text
- parseAll :: FromHttpApiData v => Text -> Form -> Either Text [v]
- parseMaybe :: FromHttpApiData v => Text -> Form -> Either Text (Maybe v)
- parseUnique :: FromHttpApiData v => Text -> Form -> Either Text v
- data FormOptions = FormOptions {- fieldLabelModifier :: String -> String
 
- defaultFormOptions :: FormOptions
Documentation
>>>:set -XDeriveGeneric>>>:set -XOverloadedLists>>>:set -XOverloadedStrings>>>:set -XFlexibleContexts>>>:set -XScopedTypeVariables>>>:set -XTypeFamilies>>>import Data.Char (toLower)
>>>data Person = Person { name :: String, age :: Int } deriving (Show, Generic)>>>instance ToForm Person>>>instance FromForm Person
>>>data Post = Post { title :: String, subtitle :: Maybe String, comments :: [String]} deriving (Generic, Show)>>>instance ToForm Post>>>instance FromForm Post
>>>data Project = Project { projectName :: String, projectSize :: Int } deriving (Generic, Show)>>>let myOptions = FormOptions { fieldLabelModifier = map toLower . drop (length ("project" :: String)) }>>>instance ToForm Project where toForm = genericToForm myOptions>>>instance FromForm Project where fromForm = genericFromForm myOptions
class ToFormKey k where Source #
Minimal complete definition
Instances
class FromFormKey k where Source #
Minimal complete definition
Instances
The contents of a form, not yet URL-encoded.
Form can be URL-encoded with urlEncodeForm and URL-decoded with urlDecodeForm.
Convert a value into Form.
An example type and instance:
{-# LANGUAGE OverloadedLists #-}
data Person = Person
  { name :: String
  , age  :: Int }
instance ToForm Person where
  toForm person =
    [ ("name", toQueryParam (name person))
    , ("age", toQueryParam (age person)) ]
Instead of manually writing ToFormtoForm
To do that, simply add deriving  clause to your datatype
 and declare a GenericToForm instance for your datatype without
 giving definition for toForm.
For instance, the previous example can be simplified into this:
data Person = Person
  { name :: String
  , age  :: Int
  } deriving (Generic)
instance ToForm Person
The default implementation of toForm is genericToForm.
fromEntriesByKey :: (ToFormKey k, ToHttpApiData v) => [(k, [v])] -> Form Source #
Convert a list of entries groupped by key into a Form.
>>>fromEntriesByKey [("name",["Nick"]),("color",["red","blue"])]fromList [("color","red"),("color","blue"),("name","Nick")]
type family NotSupported (cls :: k1) (a :: k2) (reason :: Symbol) :: Constraint where ... Source #
Equations
| NotSupported cls a reason = TypeError (((((((Text "Cannot derive a Generic-based " :<>: ShowType cls) :<>: Text " instance for ") :<>: ShowType a) :<>: Text ".") :$$: (((ShowType a :<>: Text " ") :<>: Text reason) :<>: Text ",")) :$$: ((Text "but Generic-based " :<>: ShowType cls) :<>: Text " instances can be derived only for records")) :$$: Text "(i.e. product types with named fields).") | 
genericToForm :: forall a. (Generic a, GToForm a (Rep a)) => FormOptions -> a -> Form Source #
A Generic-based implementation of toForm.
 This is used as a default implementation in ToForm.
Note that this only works for records (i.e. product data types with named fields):
data Person = Person
  { name :: String
  , age  :: Int
  } deriving (Generic)
In this implementation each field's value gets encoded using toQueryParam.
 Two field types are exceptions:
- for values of type MaybeaFormonly when it isJustxtoQueryParamxNothingvalues are omitted from theForm;
- for values of type [a](except[) an entry is added for every item in the list; if the list is empty no entries are added to theChar]Form;
Here's an example:
data Post = Post
  { title    :: String
  , subtitle :: Maybe String
  , comments :: [String]
  } deriving (Generic, Show)
instance ToForm Post
>>>urlEncodeAsForm Post { title = "Test", subtitle = Nothing, comments = ["Nice post!", "+1"] }"comments=Nice%20post%21&comments=%2B1&title=Test"
class GToForm t (f :: * -> *) where Source #
Minimal complete definition
Instances
| (GToForm k t f, GToForm k t g) => GToForm k t ((:*:) * f g) Source # | |
| NotSupported (* -> Constraint) k ToForm t "is a sum type" => GToForm k t ((:+:) * f g) Source # | |
| Selector Meta s => GToForm k t (M1 * S s (K1 * i String)) Source # | |
| (Selector Meta s, ToHttpApiData c) => GToForm k t (M1 * S s (K1 * i [c])) Source # | |
| (Selector Meta s, ToHttpApiData c) => GToForm k t (M1 * S s (K1 * i (Maybe c))) Source # | |
| (Selector Meta s, ToHttpApiData c) => GToForm k t (M1 * S s (K1 * i c)) Source # | |
| GToForm k t f => GToForm k t (M1 * C x f) Source # | |
| GToForm k t f => GToForm k t (M1 * D x f) Source # | |
class FromForm a where Source #
Parse Form into a value.
An example type and instance:
data Person = Person
  { name :: String
  , age  :: Int }
instance FromForm Person where
  fromForm f = Person
    <$> parseUnique "name" f
    <*> parseUnique "age"  f
Instead of manually writing FromFormfromForm
To do that, simply add deriving  clause to your datatype
 and declare a GenericFromForm instance for your datatype without
 giving definition for fromForm.
For instance, the previous example can be simplified into this:
data Person = Person
  { name :: String
  , age  :: Int
  } deriving (Generic)
instance FromForm Person
The default implementation of fromForm is genericFromForm.
 It only works for records and it will use parseQueryParam for each field's value.
Methods
fromForm :: Form -> Either Text a Source #
Parse Form into a value.
fromForm :: (Generic a, GFromForm a (Rep a)) => Form -> Either Text a Source #
Parse Form into a value.
Instances
| FromForm Form Source # | |
| (FromFormKey k, FromHttpApiData v) => FromForm [(k, v)] Source # | |
| FromHttpApiData v => FromForm (IntMap [v]) Source # | |
| (Ord k, FromFormKey k, FromHttpApiData v) => FromForm (Map k [v]) Source # | |
| (Eq k, Hashable k, FromFormKey k, FromHttpApiData v) => FromForm (HashMap k [v]) Source # | |
toEntriesByKey :: (FromFormKey k, FromHttpApiData v) => Form -> Either Text [(k, [v])] Source #
Parse a Form into a list of entries groupped by key.
>>>toEntriesByKey [("name", "Nick"), ("color", "red"), ("color", "white")] :: Either Text [(Text, [Text])]Right [("color",["red","white"]),("name",["Nick"])]
genericFromForm :: forall a. (Generic a, GFromForm a (Rep a)) => FormOptions -> Form -> Either Text a Source #
A Generic-based implementation of fromForm.
 This is used as a default implementation in FromForm.
Note that this only works for records (i.e. product data types with named fields):
data Person = Person
  { name :: String
  , age  :: Int
  } deriving (Generic)
In this implementation each field's value gets decoded using parseQueryParam.
 Two field types are exceptions:
- for values of type MaybeaFormand the is decoded withparseQueryParam; if no entry is present result isNothing;
- for values of type [a](except[) all entries are parsed to produce a list of parsed values;Char]
Here's an example:
data Post = Post
  { title    :: String
  , subtitle :: Maybe String
  , comments :: [String]
  } deriving (Generic, Show)
instance FromForm Post
>>>urlDecodeAsForm "comments=Nice%20post%21&comments=%2B1&title=Test" :: Either Text PostRight (Post {title = "Test", subtitle = Nothing, comments = ["Nice post!","+1"]})
class GFromForm t (f :: * -> *) where Source #
Minimal complete definition
Instances
| (GFromForm k t f, GFromForm k t g) => GFromForm k t ((:*:) * f g) Source # | |
| NotSupported (* -> Constraint) k FromForm t "is a sum type" => GFromForm k t ((:+:) * f g) Source # | |
| Selector Meta s => GFromForm k t (M1 * S s (K1 * i String)) Source # | |
| (Selector Meta s, FromHttpApiData c) => GFromForm k t (M1 * S s (K1 * i [c])) Source # | |
| (Selector Meta s, FromHttpApiData c) => GFromForm k t (M1 * S s (K1 * i (Maybe c))) Source # | |
| (Selector Meta s, FromHttpApiData c) => GFromForm k t (M1 * S s (K1 * i c)) Source # | |
| GFromForm k t f => GFromForm k t (M1 * C x f) Source # | |
| GFromForm k t f => GFromForm k t (M1 * D x f) Source # | |
urlEncodeForm :: Form -> ByteString Source #
Encode a Form to an application/x-www-form-urlencoded ByteString.
Key-value pairs get encoded to key=value and separated by &:
>>>urlEncodeForm [("name", "Julian"), ("lastname", "Arni")]"lastname=Arni&name=Julian"
Keys with empty values get encoded to just key (without the = sign):
>>>urlEncodeForm [("is_test", "")]"is_test"
Empty keys are allowed too:
>>>urlEncodeForm [("", "foobar")]"=foobar"
However, if not key and value are empty, the key-value pair is ignored.
 (This prevents urlDecodeForm . urlEncodeForm
>>>urlEncodeForm [("", "")]""
Everything is escaped with escapeURIString isUnreserved
>>>urlEncodeForm [("fullname", "Andres Löh")]"fullname=Andres%20L%C3%B6h"
urlDecodeForm :: ByteString -> Either Text Form Source #
Decode an application/x-www-form-urlencoded ByteString to a Form.
Key-value pairs get decoded normally:
>>>urlDecodeForm "name=Greg&lastname=Weber"Right (fromList [("lastname","Weber"),("name","Greg")])
Keys with no values get decoded to pairs with empty values.
>>>urlDecodeForm "is_test"Right (fromList [("is_test","")])
Empty keys are allowed:
>>>urlDecodeForm "=foobar"Right (fromList [("","foobar")])
The empty string gets decoded into an empty Form:
>>>urlDecodeForm ""Right (fromList [])
Everything is un-escaped with unEscapeString:
>>>urlDecodeForm "fullname=Andres%20L%C3%B6h"Right (fromList [("fullname","Andres L\246h")])
Improperly formed strings result in an error:
>>>urlDecodeForm "this=has=too=many=equals"Left "not a valid pair: this=has=too=many=equals"
urlDecodeAsForm :: FromForm a => ByteString -> Either Text a Source #
This is a convenience function for decoding a
 application/x-www-form-urlencoded ByteString directly to a datatype
 that has an instance of FromForm.
This is effectively fromForm <=< urlDecodeForm
>>>urlDecodeAsForm "name=Dennis&age=22" :: Either Text PersonRight (Person {name = "Dennis", age = 22})
urlEncodeAsForm :: ToForm a => a -> ByteString Source #
This is a convenience function for encoding a datatype that has instance
 of ToForm directly to a application/x-www-form-urlencoded
 ByteString.
This is effectively urlEncodeForm . toForm
>>>urlEncodeAsForm Person {name = "Dennis", age = 22}"age=22&name=Dennis"
lookupAll :: Text -> Form -> [Text] Source #
Find all values corresponding to a given key in a Form.
>>>lookupAll "name" [][]>>>lookupAll "name" [("name", "Oleg")]["Oleg"]>>>lookupAll "name" [("name", "Oleg"), ("name", "David")]["Oleg","David"]
lookupMaybe :: Text -> Form -> Either Text (Maybe Text) Source #
Lookup an optional value for a key. Fail if there is more than one value.
>>>lookupMaybe "name" []Right Nothing>>>lookupMaybe "name" [("name", "Oleg")]Right (Just "Oleg")>>>lookupMaybe "name" [("name", "Oleg"), ("name", "David")]Left "Duplicate key \"name\""
lookupUnique :: Text -> Form -> Either Text Text Source #
Lookup a unique value for a key. Fail if there is zero or more than one value.
>>>lookupUnique "name" []Left "Could not find key \"name\"">>>lookupUnique "name" [("name", "Oleg")]Right "Oleg">>>lookupUnique "name" [("name", "Oleg"), ("name", "David")]Left "Duplicate key \"name\""
parseAll :: FromHttpApiData v => Text -> Form -> Either Text [v] Source #
Lookup all values for a given key in a Form and parse them with parseQueryParams.
>>>parseAll "age" [] :: Either Text [Word8]Right []>>>parseAll "age" [("age", "8"), ("age", "seven")] :: Either Text [Word8]Left "could not parse: `seven' (input does not start with a digit)">>>parseAll "age" [("age", "8"), ("age", "777")] :: Either Text [Word8]Left "out of bounds: `777' (should be between 0 and 255)">>>parseAll "age" [("age", "12"), ("age", "25")] :: Either Text [Word8]Right [12,25]
parseMaybe :: FromHttpApiData v => Text -> Form -> Either Text (Maybe v) Source #
Lookup an optional value for a given key and parse it with parseQueryParam.
 Fail if there is more than one value for the key.
>>>parseMaybe "age" [] :: Either Text (Maybe Word8)Right Nothing>>>parseMaybe "age" [("age", "12"), ("age", "25")] :: Either Text (Maybe Word8)Left "Duplicate key \"age\"">>>parseMaybe "age" [("age", "seven")] :: Either Text (Maybe Word8)Left "could not parse: `seven' (input does not start with a digit)">>>parseMaybe "age" [("age", "777")] :: Either Text (Maybe Word8)Left "out of bounds: `777' (should be between 0 and 255)">>>parseMaybe "age" [("age", "7")] :: Either Text (Maybe Word8)Right (Just 7)
parseUnique :: FromHttpApiData v => Text -> Form -> Either Text v Source #
Lookup a unique value for a given key and parse it with parseQueryParam.
 Fail if there is zero or more than one value for the key.
>>>parseUnique "age" [] :: Either Text Word8Left "Could not find key \"age\"">>>parseUnique "age" [("age", "12"), ("age", "25")] :: Either Text Word8Left "Duplicate key \"age\"">>>parseUnique "age" [("age", "seven")] :: Either Text Word8Left "could not parse: `seven' (input does not start with a digit)">>>parseUnique "age" [("age", "777")] :: Either Text Word8Left "out of bounds: `777' (should be between 0 and 255)">>>parseUnique "age" [("age", "7")] :: Either Text Word8Right 7
data FormOptions Source #
Generic-based deriving options for ToForm and FromForm.
A common use case for non-default FormOptions
 is to strip a prefix off of field labels:
data Project = Project
  { projectName :: String
  , projectSize :: Int
  } deriving (Generic, Show)
myOptions :: FormOptions
myOptions = FormOptions
 { fieldLabelModifier = map toLower . drop (length "project") }
instance ToForm Project where
  toForm = genericToForm myOptions
instance FromForm Project where
  fromForm = genericFromForm myOptions
>>>urlEncodeAsForm Project { projectName = "http-api-data", projectSize = 172 }"size=172&name=http-api-data">>>urlDecodeAsForm "name=http-api-data&size=172" :: Either Text ProjectRight (Project {projectName = "http-api-data", projectSize = 172})
Constructors
| FormOptions | |
| Fields 
 | |
defaultFormOptions :: FormOptions Source #
Default encoding FormOptions.
FormOptions{fieldLabelModifier= id }