wai-request-spec-0.10.2.4: Declarative request parsing

CopyrightAllele Dev 2015
LicenseBSD-3
Maintainerallele.dev@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Network.Wai.RequestSpec

Contents

Description

 

Synopsis

Primitive parsing data types

data Result a Source #

Constructors

Failure Error 
Success a 

Instances

Monad Result Source # 

Methods

(>>=) :: Result a -> (a -> Result b) -> Result b #

(>>) :: Result a -> Result b -> Result b #

return :: a -> Result a #

fail :: String -> Result a #

Functor Result Source # 

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Applicative Result Source # 

Methods

pure :: a -> Result a #

(<*>) :: Result (a -> b) -> Result a -> Result b #

(*>) :: Result a -> Result b -> Result b #

(<*) :: Result a -> Result b -> Result a #

Show a => Show (Result a) Source # 

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

data P a Source #

Instances

Monad P Source # 

Methods

(>>=) :: P a -> (a -> P b) -> P b #

(>>) :: P a -> P b -> P b #

return :: a -> P a #

fail :: String -> P a #

Functor P Source # 

Methods

fmap :: (a -> b) -> P a -> P b #

(<$) :: a -> P b -> P a #

Applicative P Source # 

Methods

pure :: a -> P a #

(<*>) :: P (a -> b) -> P a -> P b #

(*>) :: P a -> P b -> P b #

(<*) :: P a -> P b -> P a #

Alternative P Source # 

Methods

empty :: P a #

(<|>) :: P a -> P a -> P a #

some :: P a -> P [a] #

many :: P a -> P [a] #

MonadPlus P Source # 

Methods

mzero :: P a #

mplus :: P a -> P a -> P a #

Monoid a => Monoid (P a) Source # 

Methods

mempty :: P a #

mappend :: P a -> P a -> P a #

mconcat :: [P a] -> P a #

Primitive parsing functions

parse :: (a -> P b) -> a -> Result b Source #

parseMaybe :: (a -> P b) -> a -> Maybe b Source #

parseEither :: (a -> P b) -> a -> Either Error b Source #

Error generation and parser annotation

(<?>) :: P a -> Text -> P a Source #

missing :: Loc -> P a Source #

Error types

data Loc Source #

Constructors

Header (CI Text) 
Param Text 

Instances

Show Loc Source # 

Methods

showsPrec :: Int -> Loc -> ShowS #

show :: Loc -> String #

showList :: [Loc] -> ShowS #

Generating parsing environment

toEnv :: Request -> Env Source #

Construct an Env without parsing any form parameters This is ideal if you're not consuming any form data.

toEnvWithForm :: Request -> [(Text, Text)] -> Env Source #

Construct an Env from a Request and an association list of form parameters If a framework exposes parameters in this fashion (Spock, Scotty), use this over toEnvRaw. It's likely the framework consumes the request body when data is sent along using content-type 'application/x-www-form-urlencoded'

toEnvRaw :: Request -> ByteString -> Env Source #

Expects form data via request body ByteString This is appropriate if you're programming with raw Network.Wai NOTE: if you're expecting form data, and the form data is in an invalid format this will happily construct an Env with empty form data

Parser driving type class

data Env Source #

class FromEnv a where Source #

Allows for the parsing of a data type a from an Env

Minimal complete definition

fromEnv

Methods

fromEnv :: Env -> P a Source #

Derived combinators, query parameters

intQ :: (Read a, Integral a) => Text -> Env -> P a Source #

Require a parameter as an integral type

boolQ :: Text -> Env -> P Bool Source #

Require a parameter as a boolean: "true" | "false"

floatQ :: (Read a, Fractional a) => Text -> Env -> P a Source #

Require a parameter as a fractional type

textQ :: Text -> Env -> P Text Source #

Require a parameter as text

bytesQ :: (Text -> ByteString) -> Text -> Env -> P ByteString Source #

Require a parameter as bytes, applying the encoding function f

intQM :: (Read a, Integral a) => Text -> Env -> P (Maybe a) Source #

Optional parameter as integral

floatQM :: (Read a, Fractional a) => Text -> Env -> P (Maybe a) Source #

Optional parameter as fractional

textQM :: Text -> Env -> P (Maybe Text) Source #

Optional parameter as text

bytesQM :: (Text -> ByteString) -> Text -> Env -> P (Maybe ByteString) Source #

Optional header as bytes, applying the encoding function f

Derived combinators, form parameters

intF :: (Read a, Integral a) => Text -> Env -> P a Source #

Require a parameter as an integral type

boolF :: Text -> Env -> P Bool Source #

Require a parameter as a boolean: "true" | "false"

floatF :: (Read a, Fractional a) => Text -> Env -> P a Source #

Require a parameter as a fractional type

textF :: Text -> Env -> P Text Source #

Require a parameter as text

bytesF :: (Text -> ByteString) -> Text -> Env -> P ByteString Source #

Require a parameter as bytes, applying the encoding function f

intFM :: (Read a, Integral a) => Text -> Env -> P (Maybe a) Source #

Optional parameter as integral

floatFM :: (Read a, Fractional a) => Text -> Env -> P (Maybe a) Source #

Optional parameter as fractional

textFM :: Text -> Env -> P (Maybe Text) Source #

Optional parameter as text

bytesFM :: (Text -> ByteString) -> Text -> Env -> P (Maybe ByteString) Source #

Optional header as bytes, applying the encoding function f

Derived combinators, headers

intH :: (Integral a, Read a) => CI Text -> Env -> P a Source #

Require a header as an integral type

boolH :: CI Text -> Env -> P Bool Source #

Require a header as a boolean: "true" | "false"

floatH :: (Fractional a, Read a) => CI Text -> Env -> P a Source #

Require a header a fractional type

textH :: CI Text -> Env -> P Text Source #

Require a header as text

bytesH :: (Text -> ByteString) -> CI Text -> Env -> P ByteString Source #

Require a header as bytes, applying the encoding function f

intHM :: (Integral a, Read a) => CI Text -> Env -> P (Maybe a) Source #

Optional header as integral

floatHM :: (Fractional a, Read a) => CI Text -> Env -> P (Maybe a) Source #

Optional header as floating

textHM :: CI Text -> Env -> P (Maybe Text) Source #

Optional header as text

bytesHM :: (Text -> ByteString) -> CI Text -> Env -> P (Maybe ByteString) Source #

Optional header as bytes, applying the encoding function f

Derived combinators, utility

choice :: [P a] -> P a Source #

Combine a series of alternatives choice [a, b, c] == a | b | c | empty