{-# LANGUAGE CPP #-} {-| Module : Network.Wai.RequestSpec.Combinators Description : Derived parser combinators Copyright : Allele Dev 2015 License : BSD-3 Maintainer : allele.dev@gmail.com Stability : experimental Portability : POSIX -} module Network.Wai.RequestSpec.Combinators ( intQ, boolQ, floatQ, textQ, bytesQ, textQM, intQM, floatQM, bytesQM, intF, boolF, floatF, textF, bytesF, textFM, intFM, floatFM, bytesFM, intH, boolH, floatH, textH, bytesH, textHM, intHM, floatHM, bytesHM, choice ) where #if __GLASGOW_HASKELL__ < 710 import Control.Applicative #endif import Data.ByteString import Data.CaseInsensitive import Data.Foldable (asum) import Data.Text import Network.Wai.RequestSpec.Internal.Combinators import Network.Wai.RequestSpec.Internal.Env import Network.Wai.RequestSpec.Internal.Parser ---------------------------------------------------------------------- -- Typed Query Parameter Access -- ---------------------------------------------------------------------- -- | -- Require a parameter as an integral type intQ :: (Read a, Integral a) => Text -> Env -> P a intQ = qParam int -- | -- Require a parameter as a boolean: "true" | "false" boolQ :: Text -> Env -> P Bool boolQ = qParam bool -- | -- Require a parameter as a fractional type floatQ :: (Read a, Fractional a) => Text -> Env -> P a floatQ = qParam float -- | -- Require a parameter as text textQ :: Text -> Env -> P Text textQ = qParam pure -- | -- Require a parameter as bytes, applying the encoding function `f` bytesQ :: (Text -> ByteString) -> Text -> Env -> P ByteString bytesQ f = qParam (pure . f) -- | -- Optional parameter as integral intQM :: (Read a, Integral a) => Text -> Env -> P (Maybe a) intQM = qParamM int -- | -- Optional parameter as fractional floatQM :: (Read a, Fractional a) => Text -> Env -> P (Maybe a) floatQM = qParamM float -- | -- Optional parameter as text textQM :: Text -> Env -> P (Maybe Text) textQM = qParamM pure -- | -- Optional header as bytes, applying the encoding function `f` bytesQM :: (Text -> ByteString) -> Text -> Env -> P (Maybe ByteString) bytesQM f = qParamM (pure . f) ---------------------------------------------------------------------- -- Typed Form Parameter Access -- ---------------------------------------------------------------------- -- | -- Require a parameter as an integral type intF :: (Read a, Integral a) => Text -> Env -> P a intF = fParam int -- | -- Require a parameter as a boolean: "true" | "false" boolF :: Text -> Env -> P Bool boolF = fParam bool -- | -- Require a parameter as a fractional type floatF :: (Read a, Fractional a) => Text -> Env -> P a floatF = fParam float -- | -- Require a parameter as text textF :: Text -> Env -> P Text textF = fParam pure -- | -- Require a parameter as bytes, applying the encoding function `f` bytesF :: (Text -> ByteString) -> Text -> Env -> P ByteString bytesF f = fParam (pure . f) -- | -- Optional parameter as integral intFM :: (Read a, Integral a) => Text -> Env -> P (Maybe a) intFM = fParamM int -- | -- Optional parameter as fractional floatFM :: (Read a, Fractional a) => Text -> Env -> P (Maybe a) floatFM = fParamM float -- | -- Optional parameter as text textFM :: Text -> Env -> P (Maybe Text) textFM = fParamM pure -- | -- Optional header as bytes, applying the encoding function `f` bytesFM :: (Text -> ByteString) -> Text -> Env -> P (Maybe ByteString) bytesFM f = fParamM (pure . f) ---------------------------------------------------------------------- -- Typed Header Access -- ---------------------------------------------------------------------- -- | -- Require a header as an integral type intH :: (Integral a, Read a) => CI Text -> Env -> P a intH = header int -- | -- Require a header as a boolean: "true" | "false" boolH :: CI Text -> Env -> P Bool boolH = header bool -- | -- Require a header a fractional type floatH :: (Fractional a, Read a) => CI Text -> Env -> P a floatH = header float -- | -- Require a header as text textH :: CI Text -> Env -> P Text textH = header pure -- | -- Require a header as bytes, applying the encoding function `f` bytesH :: (Text -> ByteString) -> CI Text -> Env -> P ByteString bytesH f = header (pure . f) -- | -- Optional header as text textHM :: CI Text -> Env -> P (Maybe Text) textHM = headerM pure -- | -- Optional header as integral intHM :: (Integral a, Read a) => CI Text -> Env -> P (Maybe a) intHM = headerM int -- | -- Optional header as floating floatHM :: (Fractional a, Read a) => CI Text -> Env -> P (Maybe a) floatHM = headerM float -- | -- Optional header as bytes, applying the encoding function `f` bytesHM :: (Text -> ByteString) -> CI Text -> Env -> P (Maybe ByteString) bytesHM f = headerM (pure . f) ---------------------------------------------------------------------- -- Utility Combinators -- ---------------------------------------------------------------------- -- | -- Combine a series of alternatives -- choice [a, b, c] == a <|> b <|> c <|> empty choice :: [P a] -> P a choice = asum