{-# LANGUAGE CPP                  #-}
{-# LANGUAGE DefaultSignatures    #-}
{-# LANGUAGE DeriveDataTypeable   #-}
{-# LANGUAGE DeriveFoldable       #-}
{-# LANGUAGE DeriveFunctor        #-}
{-# LANGUAGE DeriveTraversable    #-}
{-# LANGUAGE FlexibleInstances    #-}
{-# LANGUAGE KindSignatures       #-}
{-# LANGUAGE OverloadedStrings    #-}
{-# LANGUAGE PolyKinds            #-}
{-# LANGUAGE ScopedTypeVariables  #-}
{-# LANGUAGE TypeSynonymInstances #-}
-- |
-- Convert Haskell values to and from HTTP API data
-- such as URL pieces, headers and query parameters.
module Web.Internal.HttpApiData where

import           Control.Applicative          (Const(Const))
import           Control.Arrow                (left, (&&&))
import           Control.Monad                ((<=<))
import           Data.ByteString              (ByteString)
import qualified Data.ByteString              as BS
import qualified Data.ByteString.Builder      as BS
import qualified Data.ByteString.Lazy         as LBS
import           Data.Coerce                  (coerce)
import           Data.Data                    (Data)
import qualified Data.Fixed                   as F
import           Data.Functor.Identity        (Identity(Identity))
import           Data.Int                     (Int16, Int32, Int64, Int8)
import           Data.Kind                    (Type)
import qualified Data.Map                     as Map
import           Data.Monoid                  (All (..), Any (..), Dual (..),
                                               First (..), Last (..),
                                               Product (..), Sum (..))
import           Data.Semigroup               (Semigroup (..))
import qualified Data.Semigroup               as Semi
import           Data.Tagged                  (Tagged (..))
import           Data.Text                    (Text)
import qualified Data.Text                    as T
import           Data.Text.Encoding           (decodeUtf8', decodeUtf8With,
                                               encodeUtf8)
import           Data.Text.Encoding.Error     (lenientDecode)
import qualified Data.Text.Lazy               as L
import           Data.Text.Lazy.Builder       (Builder, toLazyText)
import           Data.Text.Read               (Reader, decimal, rational,
                                               signed)
import qualified Data.Time.ToText             as TT
import qualified Data.Time.FromText           as FT
import           Data.Time.Compat             (Day, LocalTime,
                                               NominalDiffTime, TimeOfDay,
                                               UTCTime, ZonedTime, DayOfWeek (..),
                                               nominalDiffTimeToSeconds,
                                               secondsToNominalDiffTime)
import           Data.Time.Calendar.Month.Compat (Month)
import           Data.Time.Calendar.Quarter.Compat (Quarter, QuarterOfYear (..))
import           Data.Typeable                (Typeable)
import qualified Data.UUID.Types              as UUID
import           Data.Version                 (Version, parseVersion,
                                               showVersion)
import           Data.Void                    (Void, absurd)
import           Data.Word                    (Word16, Word32, Word64, Word8)
import qualified Network.HTTP.Types           as H
import           Numeric.Natural              (Natural)
import           Text.ParserCombinators.ReadP (readP_to_S)
import           Text.Read                    (readMaybe)
import           Web.Cookie                   (SetCookie, parseSetCookie,
                                               renderSetCookie)

#if USE_TEXT_SHOW
import           TextShow                     (TextShow, showt)
#endif

-- $setup
-- >>> :set -XOverloadedStrings
-- >>> import Data.Text (Text)
-- >>> import Data.Word (Word8)
-- >>> import Data.Text.Read (decimal)
-- >>> import Data.Time.Compat
-- >>> import Data.Time.Calendar.Month.Compat
-- >>> import Data.Time.Calendar.Quarter.Compat
-- >>> import Data.Version
-- >>> import Web.Cookie (SetCookie)
-- >>> data BasicAuthToken = BasicAuthToken Text deriving (Show)
-- >>> instance FromHttpApiData BasicAuthToken where parseHeader h = BasicAuthToken <$> parseHeaderWithPrefix "Basic " h; parseQueryParam p = BasicAuthToken <$> parseQueryParam p

-- | Convert value to HTTP API data.
--
-- __WARNING__: Do not derive this using @DeriveAnyClass@ as the generated
-- instance will loop indefinitely.
class ToHttpApiData a where
  {-# MINIMAL toUrlPiece | toQueryParam #-}
  -- | Convert to URL path piece.
  toUrlPiece :: a -> Text
  toUrlPiece = a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam

  -- | Convert to a URL path piece, making sure to encode any special chars.
  -- The default definition uses @'H.urlEncodeBuilder' 'False'@
  -- but this may be overriden with a more efficient version.
  toEncodedUrlPiece :: a -> BS.Builder
  toEncodedUrlPiece = Bool -> ByteString -> Builder
H.urlEncodeBuilder Bool
False (ByteString -> Builder) -> (a -> ByteString) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 (Text -> ByteString) -> (a -> Text) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece

  -- | Convert to HTTP header value.
  toHeader :: a -> ByteString
  toHeader = Text -> ByteString
encodeUtf8 (Text -> ByteString) -> (a -> Text) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece

  -- | Convert to query param value.
  toQueryParam :: a -> Text
  toQueryParam = a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece

  -- | Convert to URL query param,
  -- The default definition uses @'H.urlEncodeBuilder' 'True'@
  -- but this may be overriden with a more efficient version.
  --
  -- @since 0.5.1
  toEncodedQueryParam :: a -> BS.Builder
  toEncodedQueryParam = Bool -> ByteString -> Builder
H.urlEncodeBuilder Bool
True (ByteString -> Builder) -> (a -> ByteString) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 (Text -> ByteString) -> (a -> Text) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam

-- | Parse value from HTTP API data.
--
-- __WARNING__: Do not derive this using @DeriveAnyClass@ as the generated
-- instance will loop indefinitely.
class FromHttpApiData a where
  {-# MINIMAL parseUrlPiece | parseQueryParam #-}
  -- | Parse URL path piece.
  parseUrlPiece :: Text -> Either Text a
  parseUrlPiece = Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam

  -- | Parse HTTP header value.
  parseHeader :: ByteString -> Either Text a
  parseHeader = Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece (Text -> Either Text a)
-> (ByteString -> Either Text Text) -> ByteString -> Either Text a
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< ((UnicodeException -> Text)
-> Either UnicodeException Text -> Either Text Text
forall b c d. (b -> c) -> Either b d -> Either c d
forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either b d) (Either c d)
left (String -> Text
T.pack (String -> Text)
-> (UnicodeException -> String) -> UnicodeException -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnicodeException -> String
forall a. Show a => a -> String
show) (Either UnicodeException Text -> Either Text Text)
-> (ByteString -> Either UnicodeException Text)
-> ByteString
-> Either Text Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either UnicodeException Text
decodeUtf8')

  -- | Parse query param value.
  parseQueryParam :: Text -> Either Text a
  parseQueryParam = Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece

-- | Convert multiple values to a list of URL pieces.
--
-- >>> toUrlPieces [1, 2, 3] :: [Text]
-- ["1","2","3"]
toUrlPieces :: (Functor t, ToHttpApiData a) => t a -> t Text
toUrlPieces :: forall (t :: * -> *) a.
(Functor t, ToHttpApiData a) =>
t a -> t Text
toUrlPieces = (a -> Text) -> t a -> t Text
forall a b. (a -> b) -> t a -> t b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece

-- | Parse multiple URL pieces.
--
-- >>> parseUrlPieces ["true", "false"] :: Either Text [Bool]
-- Right [True,False]
-- >>> parseUrlPieces ["123", "hello", "world"] :: Either Text [Int]
-- Left "could not parse: `hello' (input does not start with a digit)"
parseUrlPieces :: (Traversable t, FromHttpApiData a) => t Text -> Either Text (t a)
parseUrlPieces :: forall (t :: * -> *) a.
(Traversable t, FromHttpApiData a) =>
t Text -> Either Text (t a)
parseUrlPieces = (Text -> Either Text a) -> t Text -> Either Text (t a)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b)
traverse Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece

-- | Convert multiple values to a list of query parameter values.
--
-- >>> toQueryParams [fromGregorian 2015 10 03, fromGregorian 2015 12 01] :: [Text]
-- ["2015-10-03","2015-12-01"]
toQueryParams :: (Functor t, ToHttpApiData a) => t a -> t Text
toQueryParams :: forall (t :: * -> *) a.
(Functor t, ToHttpApiData a) =>
t a -> t Text
toQueryParams = (a -> Text) -> t a -> t Text
forall a b. (a -> b) -> t a -> t b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam

-- | Parse multiple query parameters.
--
-- >>> parseQueryParams ["1", "2", "3"] :: Either Text [Int]
-- Right [1,2,3]
-- >>> parseQueryParams ["64", "128", "256"] :: Either Text [Word8]
-- Left "out of bounds: `256' (should be between 0 and 255)"
parseQueryParams :: (Traversable t, FromHttpApiData a) => t Text -> Either Text (t a)
parseQueryParams :: forall (t :: * -> *) a.
(Traversable t, FromHttpApiData a) =>
t Text -> Either Text (t a)
parseQueryParams = (Text -> Either Text a) -> t Text -> Either Text (t a)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b)
traverse Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam

-- | Parse URL path piece in a @'Maybe'@.
--
-- >>> parseUrlPieceMaybe "12" :: Maybe Int
-- Just 12
parseUrlPieceMaybe :: FromHttpApiData a => Text -> Maybe a
parseUrlPieceMaybe :: forall a. FromHttpApiData a => Text -> Maybe a
parseUrlPieceMaybe = (Text -> Maybe a) -> (a -> Maybe a) -> Either Text a -> Maybe a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe a -> Text -> Maybe a
forall a b. a -> b -> a
const Maybe a
forall a. Maybe a
Nothing) a -> Maybe a
forall a. a -> Maybe a
Just (Either Text a -> Maybe a)
-> (Text -> Either Text a) -> Text -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece

-- | Parse HTTP header value in a @'Maybe'@.
--
-- >>> parseHeaderMaybe "hello" :: Maybe Text
-- Just "hello"
parseHeaderMaybe :: FromHttpApiData a => ByteString -> Maybe a
parseHeaderMaybe :: forall a. FromHttpApiData a => ByteString -> Maybe a
parseHeaderMaybe = (Text -> Maybe a) -> (a -> Maybe a) -> Either Text a -> Maybe a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe a -> Text -> Maybe a
forall a b. a -> b -> a
const Maybe a
forall a. Maybe a
Nothing) a -> Maybe a
forall a. a -> Maybe a
Just (Either Text a -> Maybe a)
-> (ByteString -> Either Text a) -> ByteString -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either Text a
forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader

-- | Parse query param value in a @'Maybe'@.
--
-- >>> parseQueryParamMaybe "true" :: Maybe Bool
-- Just True
parseQueryParamMaybe :: FromHttpApiData a => Text -> Maybe a
parseQueryParamMaybe :: forall a. FromHttpApiData a => Text -> Maybe a
parseQueryParamMaybe = (Text -> Maybe a) -> (a -> Maybe a) -> Either Text a -> Maybe a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe a -> Text -> Maybe a
forall a b. a -> b -> a
const Maybe a
forall a. Maybe a
Nothing) a -> Maybe a
forall a. a -> Maybe a
Just (Either Text a -> Maybe a)
-> (Text -> Either Text a) -> Text -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam

-- | Default parsing error.
defaultParseError :: Text -> Either Text a
defaultParseError :: forall a. Text -> Either Text a
defaultParseError Text
input = Text -> Either Text a
forall a b. a -> Either a b
Left (Text
"could not parse: `" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
input Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"'")

-- | Convert @'Maybe'@ parser into @'Either' 'Text'@ parser with default error message.
parseMaybeTextData :: (Text -> Maybe a) -> (Text -> Either Text a)
parseMaybeTextData :: forall a. (Text -> Maybe a) -> Text -> Either Text a
parseMaybeTextData Text -> Maybe a
parse Text
input =
  case Text -> Maybe a
parse Text
input of
    Maybe a
Nothing  -> Text -> Either Text a
forall a. Text -> Either Text a
defaultParseError Text
input
    Just a
val -> a -> Either Text a
forall a b. b -> Either a b
Right a
val

#if USE_TEXT_SHOW
-- | /Lower case/.
--
-- Convert to URL piece using @'TextShow'@ instance.
-- The result is always lower cased.
--
-- >>> showTextData True
-- "true"
--
-- This can be used as a default implementation for enumeration types:
--
-- @
-- data MyData = Foo | Bar | Baz deriving (Generic)
--
-- instance TextShow MyData where
--   showt = genericShowt
--
-- instance ToHttpApiData MyData where
--   toUrlPiece = showTextData
-- @
showTextData :: TextShow a => a -> Text
showTextData = T.toLower . showt
#else
-- | /Lower case/.
--
-- Convert to URL piece using @'Show'@ instance.
-- The result is always lower cased.
--
-- >>> showTextData True
-- "true"
--
-- This can be used as a default implementation for enumeration types:
--
-- >>> data MyData = Foo | Bar | Baz deriving (Show)
-- >>> instance ToHttpApiData MyData where toUrlPiece = showTextData
-- >>> toUrlPiece Foo
-- "foo"
showTextData :: Show a => a -> Text
showTextData :: forall a. Show a => a -> Text
showTextData = Text -> Text
T.toLower (Text -> Text) -> (a -> Text) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. Show a => a -> Text
showt

-- | Like @'show'@, but returns @'Text'@.
showt :: Show a => a -> Text
showt :: forall a. Show a => a -> Text
showt = String -> Text
T.pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show
#endif

-- | /Case insensitive/.
--
-- Parse given text case insensitive and then parse the rest of the input
-- using @'parseUrlPiece'@.
--
-- >>> parseUrlPieceWithPrefix "Just " "just 10" :: Either Text Int
-- Right 10
-- >>> parseUrlPieceWithPrefix "Left " "left" :: Either Text Bool
-- Left "could not parse: `left'"
--
-- This can be used to implement @'FromHttpApiData'@ for single field constructors:
--
-- >>> data Foo = Foo Int deriving (Show)
-- >>> instance FromHttpApiData Foo where parseUrlPiece s = Foo <$> parseUrlPieceWithPrefix "Foo " s
-- >>> parseUrlPiece "foo 1" :: Either Text Foo
-- Right (Foo 1)
parseUrlPieceWithPrefix :: FromHttpApiData a => Text -> Text -> Either Text a
parseUrlPieceWithPrefix :: forall a. FromHttpApiData a => Text -> Text -> Either Text a
parseUrlPieceWithPrefix Text
pattern Text
input
  | Text -> Text
T.toLower Text
pattern Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Text
T.toLower Text
prefix = Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece Text
rest
  | Bool
otherwise                             = Text -> Either Text a
forall a. Text -> Either Text a
defaultParseError Text
input
  where
    (Text
prefix, Text
rest) = Int -> Text -> (Text, Text)
T.splitAt (Text -> Int
T.length Text
pattern) Text
input

-- | Parse given bytestring then parse the rest of the input using @'parseHeader'@.
--
-- @
-- data BasicAuthToken = BasicAuthToken Text deriving (Show)
--
-- instance FromHttpApiData BasicAuthToken where
--   parseHeader h     = BasicAuthToken \<$\> parseHeaderWithPrefix "Basic " h
--   parseQueryParam p = BasicAuthToken \<$\> parseQueryParam p
-- @
--
-- >>> parseHeader "Basic QWxhZGRpbjpvcGVuIHNlc2FtZQ==" :: Either Text BasicAuthToken
-- Right (BasicAuthToken "QWxhZGRpbjpvcGVuIHNlc2FtZQ==")
parseHeaderWithPrefix :: FromHttpApiData a => ByteString -> ByteString -> Either Text a
parseHeaderWithPrefix :: forall a.
FromHttpApiData a =>
ByteString -> ByteString -> Either Text a
parseHeaderWithPrefix ByteString
pattern ByteString
input
  | ByteString
pattern ByteString -> ByteString -> Bool
`BS.isPrefixOf` ByteString
input = ByteString -> Either Text a
forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader (Int -> ByteString -> ByteString
BS.drop (ByteString -> Int
BS.length ByteString
pattern) ByteString
input)
  | Bool
otherwise                     = Text -> Either Text a
forall a. Text -> Either Text a
defaultParseError (ByteString -> Text
forall a. Show a => a -> Text
showt ByteString
input)

-- | /Case insensitive/.
--
-- Parse given text case insensitive and then parse the rest of the input
-- using @'parseQueryParam'@.
--
-- >>> parseQueryParamWithPrefix "z" "z10" :: Either Text Int
-- Right 10
parseQueryParamWithPrefix :: FromHttpApiData a => Text -> Text -> Either Text a
parseQueryParamWithPrefix :: forall a. FromHttpApiData a => Text -> Text -> Either Text a
parseQueryParamWithPrefix Text
pattern Text
input
  | Text -> Text
T.toLower Text
pattern Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Text
T.toLower Text
prefix = Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam Text
rest
  | Bool
otherwise                             = Text -> Either Text a
forall a. Text -> Either Text a
defaultParseError Text
input
  where
    (Text
prefix, Text
rest) = Int -> Text -> (Text, Text)
T.splitAt (Text -> Int
T.length Text
pattern) Text
input

#if USE_TEXT_SHOW
-- | /Case insensitive/.
--
-- Parse values case insensitively based on @'TextShow'@ instance.
--
-- >>> parseBoundedTextData "true" :: Either Text Bool
-- Right True
-- >>> parseBoundedTextData "FALSE" :: Either Text Bool
-- Right False
--
-- This can be used as a default implementation for enumeration types:
--
-- @
-- data MyData = Foo | Bar | Baz deriving (Show, Bounded, Enum, Generic)
--
-- instance TextShow MyData where
--   showt = genericShowt
--
-- instance FromHttpApiData MyData where
--   parseUrlPiece = parseBoundedTextData
-- @
parseBoundedTextData :: (TextShow a, Bounded a, Enum a) => Text -> Either Text a
#else
-- | /Case insensitive/.
--
-- Parse values case insensitively based on @'Show'@ instance.
--
-- >>> parseBoundedTextData "true" :: Either Text Bool
-- Right True
-- >>> parseBoundedTextData "FALSE" :: Either Text Bool
-- Right False
--
-- This can be used as a default implementation for enumeration types:
--
-- >>> data MyData = Foo | Bar | Baz deriving (Show, Bounded, Enum)
-- >>> instance FromHttpApiData MyData where parseUrlPiece = parseBoundedTextData
-- >>> parseUrlPiece "foo" :: Either Text MyData
-- Right Foo
parseBoundedTextData :: (Show a, Bounded a, Enum a) => Text -> Either Text a
#endif
parseBoundedTextData :: forall a. (Show a, Bounded a, Enum a) => Text -> Either Text a
parseBoundedTextData = (a -> Text) -> Text -> Either Text a
forall a.
(Bounded a, Enum a) =>
(a -> Text) -> Text -> Either Text a
parseBoundedEnumOfI a -> Text
forall a. Show a => a -> Text
showTextData

-- | Lookup values based on a precalculated mapping of their representations.
lookupBoundedEnumOf :: (Bounded a, Enum a, Eq b) => (a -> b) -> b -> Maybe a
lookupBoundedEnumOf :: forall a b. (Bounded a, Enum a, Eq b) => (a -> b) -> b -> Maybe a
lookupBoundedEnumOf a -> b
f = (b -> [(b, a)] -> Maybe a) -> [(b, a)] -> b -> Maybe a
forall a b c. (a -> b -> c) -> b -> a -> c
flip b -> [(b, a)] -> Maybe a
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup ((a -> (b, a)) -> [a] -> [(b, a)]
forall a b. (a -> b) -> [a] -> [b]
map (a -> b
f (a -> b) -> (a -> a) -> a -> (b, a)
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& a -> a
forall a. a -> a
id) [a
forall a. Bounded a => a
minBound..a
forall a. Bounded a => a
maxBound])

-- | Parse values based on a precalculated mapping of their @'Text'@ representation.
--
-- >>> parseBoundedEnumOf toUrlPiece "true" :: Either Text Bool
-- Right True
--
-- For case insensitive parser see 'parseBoundedEnumOfI'.
parseBoundedEnumOf :: (Bounded a, Enum a) => (a -> Text) -> Text -> Either Text a
parseBoundedEnumOf :: forall a.
(Bounded a, Enum a) =>
(a -> Text) -> Text -> Either Text a
parseBoundedEnumOf = (Text -> Maybe a) -> Text -> Either Text a
forall a. (Text -> Maybe a) -> Text -> Either Text a
parseMaybeTextData ((Text -> Maybe a) -> Text -> Either Text a)
-> ((a -> Text) -> Text -> Maybe a)
-> (a -> Text)
-> Text
-> Either Text a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Text) -> Text -> Maybe a
forall a b. (Bounded a, Enum a, Eq b) => (a -> b) -> b -> Maybe a
lookupBoundedEnumOf

-- | /Case insensitive/.
--
-- Parse values case insensitively based on a precalculated mapping
-- of their @'Text'@ representations.
--
-- >>> parseBoundedEnumOfI toUrlPiece "FALSE" :: Either Text Bool
-- Right False
--
-- For case sensitive parser see 'parseBoundedEnumOf'.
parseBoundedEnumOfI :: (Bounded a, Enum a) => (a -> Text) -> Text -> Either Text a
parseBoundedEnumOfI :: forall a.
(Bounded a, Enum a) =>
(a -> Text) -> Text -> Either Text a
parseBoundedEnumOfI a -> Text
f = (a -> Text) -> Text -> Either Text a
forall a.
(Bounded a, Enum a) =>
(a -> Text) -> Text -> Either Text a
parseBoundedEnumOf (Text -> Text
T.toLower (Text -> Text) -> (a -> Text) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
f) (Text -> Either Text a) -> (Text -> Text) -> Text -> Either Text a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.toLower

-- | /Case insensitive/.
--
-- Parse values case insensitively based on @'ToHttpApiData'@ instance.
-- Uses @'toUrlPiece'@ to get possible values.
parseBoundedUrlPiece :: (ToHttpApiData a, Bounded a, Enum a) => Text -> Either Text a
parseBoundedUrlPiece :: forall a.
(ToHttpApiData a, Bounded a, Enum a) =>
Text -> Either Text a
parseBoundedUrlPiece = (a -> Text) -> Text -> Either Text a
forall a.
(Bounded a, Enum a) =>
(a -> Text) -> Text -> Either Text a
parseBoundedEnumOfI a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece

-- | /Case insensitive/.
--
-- Parse values case insensitively based on @'ToHttpApiData'@ instance.
-- Uses @'toQueryParam'@ to get possible values.
parseBoundedQueryParam :: (ToHttpApiData a, Bounded a, Enum a) => Text -> Either Text a
parseBoundedQueryParam :: forall a.
(ToHttpApiData a, Bounded a, Enum a) =>
Text -> Either Text a
parseBoundedQueryParam = (a -> Text) -> Text -> Either Text a
forall a.
(Bounded a, Enum a) =>
(a -> Text) -> Text -> Either Text a
parseBoundedEnumOfI a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam

-- | Parse values based on @'ToHttpApiData'@ instance.
-- Uses @'toHeader'@ to get possible values.
parseBoundedHeader :: (ToHttpApiData a, Bounded a, Enum a) => ByteString -> Either Text a
parseBoundedHeader :: forall a.
(ToHttpApiData a, Bounded a, Enum a) =>
ByteString -> Either Text a
parseBoundedHeader ByteString
bs = case (a -> ByteString) -> ByteString -> Maybe a
forall a b. (Bounded a, Enum a, Eq b) => (a -> b) -> b -> Maybe a
lookupBoundedEnumOf a -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toHeader ByteString
bs of
  Maybe a
Nothing -> Text -> Either Text a
forall a. Text -> Either Text a
defaultParseError (Text -> Either Text a) -> Text -> Either Text a
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ByteString -> String
forall a. Show a => a -> String
show ByteString
bs
  Just a
x  -> a -> Either Text a
forall a. a -> Either Text a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x

-- | Parse URL piece using @'Read'@ instance.
--
-- Use for types which do not involve letters:
--
-- >>> readTextData "1991-06-02" :: Either Text Day
-- Right 1991-06-02
--
-- This parser is case sensitive and will not match @'showTextData'@
-- in presence of letters:
--
-- >>> readTextData (showTextData True) :: Either Text Bool
-- Left "could not parse: `true'"
--
-- See @'parseBoundedTextData'@.
readTextData :: Read a => Text -> Either Text a
readTextData :: forall a. Read a => Text -> Either Text a
readTextData = (Text -> Maybe a) -> Text -> Either Text a
forall a. (Text -> Maybe a) -> Text -> Either Text a
parseMaybeTextData (String -> Maybe a
forall a. Read a => String -> Maybe a
readMaybe (String -> Maybe a) -> (Text -> String) -> Text -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack)

-- | Run @'Reader'@ as HTTP API data parser.
runReader :: Reader a -> Text -> Either Text a
runReader :: forall a. Reader a -> Text -> Either Text a
runReader Reader a
reader Text
input =
  case Reader a
reader Text
input of
    Left String
err          -> Text -> Either Text a
forall a b. a -> Either a b
Left (Text
"could not parse: `" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
input Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' (" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
err Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")")
    Right (a
x, Text
rest)
      | Text -> Bool
T.null Text
rest -> a -> Either Text a
forall a b. b -> Either a b
Right a
x
      | Bool
otherwise   -> Text -> Either Text a
forall a. Text -> Either Text a
defaultParseError Text
input

-- | Run @'Reader'@ to parse bounded integral value with bounds checking.
--
-- >>> parseBounded decimal "256" :: Either Text Word8
-- Left "out of bounds: `256' (should be between 0 and 255)"
parseBounded :: forall a. (Bounded a, Integral a) => Reader Integer -> Text -> Either Text a
parseBounded :: forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded Reader Integer
reader Text
input = do
  Integer
n <- Reader Integer -> Text -> Either Text Integer
forall a. Reader a -> Text -> Either Text a
runReader Reader Integer
reader Text
input
  if (Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
h Bool -> Bool -> Bool
|| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
l)
    then Text -> Either Text a
forall a b. a -> Either a b
Left  (Text
"out of bounds: `" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
input Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' (should be between " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Integer -> Text
forall a. Show a => a -> Text
showt Integer
l Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" and " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Integer -> Text
forall a. Show a => a -> Text
showt Integer
h Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")")
    else a -> Either Text a
forall a b. b -> Either a b
Right (Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
n)
  where
    l :: Integer
l = a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
minBound :: a)
    h :: Integer
h = a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
maxBound :: a)

-- | Convert to a URL-encoded path piece using 'toUrlPiece'.
-- /Note/: this function does not check if the result contains unescaped characters!
-- This function can be used to override 'toEncodedUrlPiece' as a more efficient implementation
-- when the resulting URL piece /never/ has to be escaped.
unsafeToEncodedUrlPiece :: ToHttpApiData a => a -> BS.Builder
unsafeToEncodedUrlPiece :: forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece = ByteString -> Builder
BS.byteString (ByteString -> Builder) -> (a -> ByteString) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 (Text -> ByteString) -> (a -> Text) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece

-- | Convert to a URL-encoded query param using 'toQueryParam'.
-- /Note/: this function does not check if the result contains unescaped characters!
--
-- @since 0.5.1
unsafeToEncodedQueryParam :: ToHttpApiData a => a -> BS.Builder
unsafeToEncodedQueryParam :: forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam = ByteString -> Builder
BS.byteString (ByteString -> Builder) -> (a -> ByteString) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 (Text -> ByteString) -> (a -> Text) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam

-- |
-- >>> toUrlPiece ()
-- "_"
instance ToHttpApiData () where
  toUrlPiece :: () -> Text
toUrlPiece ()
_          = Text
"_"
  toHeader :: () -> ByteString
toHeader ()
_            = ByteString
"_"
  toEncodedUrlPiece :: () -> Builder
toEncodedUrlPiece ()
_   = Builder
"_"
  toEncodedQueryParam :: () -> Builder
toEncodedQueryParam ()
_ = Builder
"_"

instance ToHttpApiData Char where
  toUrlPiece :: Char -> Text
toUrlPiece = Char -> Text
T.singleton

-- |
-- >>> toUrlPiece (Version [1, 2, 3] [])
-- "1.2.3"
instance ToHttpApiData Version where
  toUrlPiece :: Version -> Text
toUrlPiece = String -> Text
T.pack (String -> Text) -> (Version -> String) -> Version -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> String
showVersion
  toEncodedUrlPiece :: Version -> Builder
toEncodedUrlPiece = Version -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  toEncodedQueryParam :: Version -> Builder
toEncodedQueryParam = Version -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam

instance ToHttpApiData Void    where toUrlPiece :: Void -> Text
toUrlPiece = Void -> Text
forall a. Void -> a
absurd
instance ToHttpApiData Natural where toUrlPiece :: Natural -> Text
toUrlPiece = Natural -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Natural -> Builder
toEncodedUrlPiece = Natural -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Natural -> Builder
toEncodedQueryParam = Natural -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam

instance ToHttpApiData Bool     where toUrlPiece :: Bool -> Text
toUrlPiece = Bool -> Text
forall a. Show a => a -> Text
showTextData; toEncodedUrlPiece :: Bool -> Builder
toEncodedUrlPiece = Bool -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Bool -> Builder
toEncodedQueryParam = Bool -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Ordering where toUrlPiece :: Ordering -> Text
toUrlPiece = Ordering -> Text
forall a. Show a => a -> Text
showTextData; toEncodedUrlPiece :: Ordering -> Builder
toEncodedUrlPiece = Ordering -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Ordering -> Builder
toEncodedQueryParam = Ordering -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam

instance ToHttpApiData Double   where toUrlPiece :: Double -> Text
toUrlPiece = Double -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Double -> Builder
toEncodedUrlPiece = Double -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Double -> Builder
toEncodedQueryParam = Double -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Float    where toUrlPiece :: Float -> Text
toUrlPiece = Float -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Float -> Builder
toEncodedUrlPiece = Float -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Float -> Builder
toEncodedQueryParam = Float -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Int      where toUrlPiece :: Int -> Text
toUrlPiece = Int -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Int -> Builder
toEncodedUrlPiece = Int -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Int -> Builder
toEncodedQueryParam = Int -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Int8     where toUrlPiece :: Int8 -> Text
toUrlPiece = Int8 -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Int8 -> Builder
toEncodedUrlPiece = Int8 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Int8 -> Builder
toEncodedQueryParam = Int8 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Int16    where toUrlPiece :: Int16 -> Text
toUrlPiece = Int16 -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Int16 -> Builder
toEncodedUrlPiece = Int16 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Int16 -> Builder
toEncodedQueryParam = Int16 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Int32    where toUrlPiece :: Int32 -> Text
toUrlPiece = Int32 -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Int32 -> Builder
toEncodedUrlPiece = Int32 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Int32 -> Builder
toEncodedQueryParam = Int32 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Int64    where toUrlPiece :: Int64 -> Text
toUrlPiece = Int64 -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Int64 -> Builder
toEncodedUrlPiece = Int64 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Int64 -> Builder
toEncodedQueryParam = Int64 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Integer  where toUrlPiece :: Integer -> Text
toUrlPiece = Integer -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Integer -> Builder
toEncodedUrlPiece = Integer -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Integer -> Builder
toEncodedQueryParam = Integer -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Word     where toUrlPiece :: Word -> Text
toUrlPiece = Word -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Word -> Builder
toEncodedUrlPiece = Word -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Word -> Builder
toEncodedQueryParam = Word -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Word8    where toUrlPiece :: Word8 -> Text
toUrlPiece = Word8 -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Word8 -> Builder
toEncodedUrlPiece = Word8 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Word8 -> Builder
toEncodedQueryParam = Word8 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Word16   where toUrlPiece :: Word16 -> Text
toUrlPiece = Word16 -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Word16 -> Builder
toEncodedUrlPiece = Word16 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Word16 -> Builder
toEncodedQueryParam = Word16 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Word32   where toUrlPiece :: Word32 -> Text
toUrlPiece = Word32 -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Word32 -> Builder
toEncodedUrlPiece = Word32 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Word32 -> Builder
toEncodedQueryParam = Word32 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Word64   where toUrlPiece :: Word64 -> Text
toUrlPiece = Word64 -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Word64 -> Builder
toEncodedUrlPiece = Word64 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Word64 -> Builder
toEncodedQueryParam = Word64 -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam

-- | Note: this instance is not polykinded
instance F.HasResolution a => ToHttpApiData (F.Fixed (a :: Type)) where toUrlPiece :: Fixed a -> Text
toUrlPiece = Fixed a -> Text
forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Fixed a -> Builder
toEncodedUrlPiece = Fixed a -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Fixed a -> Builder
toEncodedQueryParam = Fixed a -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam

-- |
-- >>> toUrlPiece (fromGregorian 2015 10 03)
-- "2015-10-03"
instance ToHttpApiData Day where
  toUrlPiece :: Day -> Text
toUrlPiece = (Day -> Builder) -> Day -> Text
forall a. (a -> Builder) -> a -> Text
runTT Day -> Builder
TT.buildDay
  toEncodedUrlPiece :: Day -> Builder
toEncodedUrlPiece = Day -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  toEncodedQueryParam :: Day -> Builder
toEncodedQueryParam = Day -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam

-- |
-- >>> toUrlPiece $ TimeOfDay 14 55 23.1
-- "14:55:23.100"
instance ToHttpApiData TimeOfDay where
  toUrlPiece :: TimeOfDay -> Text
toUrlPiece = (TimeOfDay -> Builder) -> TimeOfDay -> Text
forall a. (a -> Builder) -> a -> Text
runTT TimeOfDay -> Builder
TT.buildTimeOfDay
  toEncodedUrlPiece :: TimeOfDay -> Builder
toEncodedUrlPiece = TimeOfDay -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  -- no toEncodedQueryParam as : is unsafe char.

-- |
-- >>> toUrlPiece $ LocalTime (fromGregorian 2015 10 03) (TimeOfDay 14 55 21.687)
-- "2015-10-03T14:55:21.687"
instance ToHttpApiData LocalTime where
  toUrlPiece :: LocalTime -> Text
toUrlPiece = (LocalTime -> Builder) -> LocalTime -> Text
forall a. (a -> Builder) -> a -> Text
runTT LocalTime -> Builder
TT.buildLocalTime
  toEncodedUrlPiece :: LocalTime -> Builder
toEncodedUrlPiece = LocalTime -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  -- no toEncodedQueryParam as : is unsafe char.

-- |
-- >>> toUrlPiece $ ZonedTime (LocalTime (fromGregorian 2015 10 03) (TimeOfDay 14 55 51.001)) utc
-- "2015-10-03T14:55:51.001Z"
--
-- >>> toUrlPiece $ ZonedTime (LocalTime (fromGregorian 2015 10 03) (TimeOfDay 14 55 51.001)) (TimeZone 120 True "EET")
-- "2015-10-03T14:55:51.001+02:00"
--
instance ToHttpApiData ZonedTime where
  toUrlPiece :: ZonedTime -> Text
toUrlPiece = (ZonedTime -> Builder) -> ZonedTime -> Text
forall a. (a -> Builder) -> a -> Text
runTT ZonedTime -> Builder
TT.buildZonedTime
  toEncodedUrlPiece :: ZonedTime -> Builder
toEncodedUrlPiece = ZonedTime -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  -- no toEncodedQueryParam as : is unsafe char.

-- |
-- >>> toUrlPiece $ UTCTime (fromGregorian 2015 10 03) 864.5
-- "2015-10-03T00:14:24.500Z"
instance ToHttpApiData UTCTime where
  toUrlPiece :: UTCTime -> Text
toUrlPiece = (UTCTime -> Builder) -> UTCTime -> Text
forall a. (a -> Builder) -> a -> Text
runTT UTCTime -> Builder
TT.buildUTCTime
  toEncodedUrlPiece :: UTCTime -> Builder
toEncodedUrlPiece = UTCTime -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  -- no toEncodedQueryParam as : is unsafe char.

-- |
-- >>> toUrlPiece Monday
-- "monday"
instance ToHttpApiData DayOfWeek where
  toUrlPiece :: DayOfWeek -> Text
toUrlPiece DayOfWeek
Monday    = Text
"monday"
  toUrlPiece DayOfWeek
Tuesday   = Text
"tuesday"
  toUrlPiece DayOfWeek
Wednesday = Text
"wednesday"
  toUrlPiece DayOfWeek
Thursday  = Text
"thursday"
  toUrlPiece DayOfWeek
Friday    = Text
"friday"
  toUrlPiece DayOfWeek
Saturday  = Text
"saturday"
  toUrlPiece DayOfWeek
Sunday    = Text
"sunday"

  toEncodedUrlPiece :: DayOfWeek -> Builder
toEncodedUrlPiece = DayOfWeek -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  toEncodedQueryParam :: DayOfWeek -> Builder
toEncodedQueryParam = DayOfWeek -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam

-- |
-- >>> toUrlPiece Q4
-- "q4"
instance ToHttpApiData QuarterOfYear where
  toUrlPiece :: QuarterOfYear -> Text
toUrlPiece = (QuarterOfYear -> Builder) -> QuarterOfYear -> Text
forall a. (a -> Builder) -> a -> Text
runTT QuarterOfYear -> Builder
TT.buildQuarterOfYear

  toEncodedUrlPiece :: QuarterOfYear -> Builder
toEncodedUrlPiece = QuarterOfYear -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  toEncodedQueryParam :: QuarterOfYear -> Builder
toEncodedQueryParam = QuarterOfYear -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam

-- |
-- >>> import Data.Time.Calendar.Quarter.Compat (Quarter (..))
-- >>> MkQuarter 8040
-- 2010-Q1
--
-- >>> toUrlPiece $ MkQuarter 8040
-- "2010-q1"
--
instance ToHttpApiData Quarter where
  toUrlPiece :: Quarter -> Text
toUrlPiece = (Quarter -> Builder) -> Quarter -> Text
forall a. (a -> Builder) -> a -> Text
runTT Quarter -> Builder
TT.buildQuarter

  toEncodedUrlPiece :: Quarter -> Builder
toEncodedUrlPiece = Quarter -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  toEncodedQueryParam :: Quarter -> Builder
toEncodedQueryParam = Quarter -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam

-- |
-- >>> import Data.Time.Calendar.Month.Compat (Month (..))
-- >>> MkMonth 24482
-- 2040-03
--
-- >>> toUrlPiece $ MkMonth 24482
-- "2040-03"
--
instance ToHttpApiData Month where
  toUrlPiece :: Month -> Text
toUrlPiece = (Month -> Builder) -> Month -> Text
forall a. (a -> Builder) -> a -> Text
runTT Month -> Builder
TT.buildMonth

  toEncodedUrlPiece :: Month -> Builder
toEncodedUrlPiece = Month -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  toEncodedQueryParam :: Month -> Builder
toEncodedQueryParam = Month -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam

instance ToHttpApiData NominalDiffTime where
  toUrlPiece :: NominalDiffTime -> Text
toUrlPiece = Pico -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece (Pico -> Text)
-> (NominalDiffTime -> Pico) -> NominalDiffTime -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTime -> Pico
nominalDiffTimeToSeconds

  toEncodedQueryParam :: NominalDiffTime -> Builder
toEncodedQueryParam = NominalDiffTime -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
  toEncodedUrlPiece :: NominalDiffTime -> Builder
toEncodedUrlPiece = NominalDiffTime -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece

instance ToHttpApiData String   where toUrlPiece :: String -> Text
toUrlPiece = String -> Text
T.pack
instance ToHttpApiData Text     where toUrlPiece :: Text -> Text
toUrlPiece = Text -> Text
forall a. a -> a
id
instance ToHttpApiData L.Text   where toUrlPiece :: Text -> Text
toUrlPiece = Text -> Text
L.toStrict

instance ToHttpApiData All where
  toUrlPiece :: All -> Text
toUrlPiece        = (Bool -> Text) -> All -> Text
forall a b. Coercible a b => a -> b
coerce (Bool -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: Bool -> Text)
  toEncodedUrlPiece :: All -> Builder
toEncodedUrlPiece = (Bool -> Builder) -> All -> Builder
forall a b. Coercible a b => a -> b
coerce (Bool -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: Bool -> BS.Builder)
  toEncodedQueryParam :: All -> Builder
toEncodedQueryParam = (Bool -> Builder) -> All -> Builder
forall a b. Coercible a b => a -> b
coerce (Bool -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: Bool -> BS.Builder)

instance ToHttpApiData Any where
  toUrlPiece :: Any -> Text
toUrlPiece        = (Bool -> Text) -> Any -> Text
forall a b. Coercible a b => a -> b
coerce (Bool -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: Bool -> Text)
  toEncodedUrlPiece :: Any -> Builder
toEncodedUrlPiece = (Bool -> Builder) -> Any -> Builder
forall a b. Coercible a b => a -> b
coerce (Bool -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: Bool -> BS.Builder)
  toEncodedQueryParam :: Any -> Builder
toEncodedQueryParam = (Bool -> Builder) -> Any -> Builder
forall a b. Coercible a b => a -> b
coerce (Bool -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: Bool -> BS.Builder)

instance ToHttpApiData a => ToHttpApiData (Dual a) where
  toUrlPiece :: Dual a -> Text
toUrlPiece        = (a -> Text) -> Dual a -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: Dual a -> Builder
toEncodedUrlPiece = (a -> Builder) -> Dual a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: Dual a -> Builder
toEncodedQueryParam = (a -> Builder) -> Dual a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)

instance ToHttpApiData a => ToHttpApiData (Sum a) where
  toUrlPiece :: Sum a -> Text
toUrlPiece        = (a -> Text) -> Sum a -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: Sum a -> Builder
toEncodedUrlPiece = (a -> Builder) -> Sum a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: Sum a -> Builder
toEncodedQueryParam = (a -> Builder) -> Sum a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)

instance ToHttpApiData a => ToHttpApiData (Product a) where
  toUrlPiece :: Product a -> Text
toUrlPiece        = (a -> Text) -> Product a -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: Product a -> Builder
toEncodedUrlPiece = (a -> Builder) -> Product a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: Product a -> Builder
toEncodedQueryParam = (a -> Builder) -> Product a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)

instance ToHttpApiData a => ToHttpApiData (First a) where
  toUrlPiece :: First a -> Text
toUrlPiece        = (Maybe a -> Text) -> First a -> Text
forall a b. Coercible a b => a -> b
coerce (Maybe a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: Maybe a -> Text)
  toEncodedUrlPiece :: First a -> Builder
toEncodedUrlPiece = (Maybe a -> Builder) -> First a -> Builder
forall a b. Coercible a b => a -> b
coerce (Maybe a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: Maybe a -> BS.Builder)
  toEncodedQueryParam :: First a -> Builder
toEncodedQueryParam = (Maybe a -> Builder) -> First a -> Builder
forall a b. Coercible a b => a -> b
coerce (Maybe a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: Maybe a -> BS.Builder)

instance ToHttpApiData a => ToHttpApiData (Last a) where
  toUrlPiece :: Last a -> Text
toUrlPiece        = (Maybe a -> Text) -> Last a -> Text
forall a b. Coercible a b => a -> b
coerce (Maybe a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: Maybe a -> Text)
  toEncodedUrlPiece :: Last a -> Builder
toEncodedUrlPiece = (Maybe a -> Builder) -> Last a -> Builder
forall a b. Coercible a b => a -> b
coerce (Maybe a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: Maybe a -> BS.Builder)
  toEncodedQueryParam :: Last a -> Builder
toEncodedQueryParam = (Maybe a -> Builder) -> Last a -> Builder
forall a b. Coercible a b => a -> b
coerce (Maybe a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: Maybe a -> BS.Builder)

instance ToHttpApiData a => ToHttpApiData (Semi.Min a) where
  toUrlPiece :: Min a -> Text
toUrlPiece        = (a -> Text) -> Min a -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: Min a -> Builder
toEncodedUrlPiece = (a -> Builder) -> Min a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: Min a -> Builder
toEncodedQueryParam = (a -> Builder) -> Min a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)

instance ToHttpApiData a => ToHttpApiData (Semi.Max a) where
  toUrlPiece :: Max a -> Text
toUrlPiece        = (a -> Text) -> Max a -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: Max a -> Builder
toEncodedUrlPiece = (a -> Builder) -> Max a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: Max a -> Builder
toEncodedQueryParam = (a -> Builder) -> Max a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)

instance ToHttpApiData a => ToHttpApiData (Semi.First a) where
  toUrlPiece :: First a -> Text
toUrlPiece        = (a -> Text) -> First a -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: First a -> Builder
toEncodedUrlPiece = (a -> Builder) -> First a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: First a -> Builder
toEncodedQueryParam = (a -> Builder) -> First a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)

instance ToHttpApiData a => ToHttpApiData (Semi.Last a) where
  toUrlPiece :: Last a -> Text
toUrlPiece        = (a -> Text) -> Last a -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: Last a -> Builder
toEncodedUrlPiece = (a -> Builder) -> Last a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: Last a -> Builder
toEncodedQueryParam = (a -> Builder) -> Last a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)

-- |
-- >>> toUrlPiece (Just "Hello")
-- "just Hello"
instance ToHttpApiData a => ToHttpApiData (Maybe a) where
  toUrlPiece :: Maybe a -> Text
toUrlPiece (Just a
x) = Text
"just " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece a
x
  toUrlPiece Maybe a
Nothing  = Text
"nothing"

-- |
-- >>> toUrlPiece (Left "err" :: Either String Int)
-- "left err"
-- >>> toUrlPiece (Right 3 :: Either String Int)
-- "right 3"
instance (ToHttpApiData a, ToHttpApiData b) => ToHttpApiData (Either a b) where
  toUrlPiece :: Either a b -> Text
toUrlPiece (Left a
x)  = Text
"left " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece a
x
  toUrlPiece (Right b
x) = Text
"right " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> b -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece b
x

-- | /Note:/ this instance works correctly for alphanumeric name and value
--
-- >>> let Right c = parseUrlPiece "SESSID=r2t5uvjq435r4q7ib3vtdjq120" :: Either Text SetCookie
-- >>> toUrlPiece c
-- "SESSID=r2t5uvjq435r4q7ib3vtdjq120"
--
-- >>> toHeader c
-- "SESSID=r2t5uvjq435r4q7ib3vtdjq120"
--
instance ToHttpApiData SetCookie where
  toUrlPiece :: SetCookie -> Text
toUrlPiece = OnDecodeError -> ByteString -> Text
decodeUtf8With OnDecodeError
lenientDecode (ByteString -> Text)
-> (SetCookie -> ByteString) -> SetCookie -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SetCookie -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toHeader
  toHeader :: SetCookie -> ByteString
toHeader = ByteString -> ByteString
LBS.toStrict (ByteString -> ByteString)
-> (SetCookie -> ByteString) -> SetCookie -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
BS.toLazyByteString (Builder -> ByteString)
-> (SetCookie -> Builder) -> SetCookie -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SetCookie -> Builder
renderSetCookie
  -- toEncodedUrlPiece = renderSetCookie -- doesn't do things.

-- | Note: this instance is not polykinded
instance ToHttpApiData a => ToHttpApiData (Tagged (b :: Type) a) where
  toUrlPiece :: Tagged b a -> Text
toUrlPiece        = (a -> Text) -> Tagged b a -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toHeader :: Tagged b a -> ByteString
toHeader          = (a -> ByteString) -> Tagged b a -> ByteString
forall a b. Coercible a b => a -> b
coerce (a -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toHeader :: a -> ByteString)
  toQueryParam :: Tagged b a -> Text
toQueryParam      = (a -> Text) -> Tagged b a -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam :: a -> Text)
  toEncodedUrlPiece :: Tagged b a -> Builder
toEncodedUrlPiece = (a -> Builder) -> Tagged b a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece ::  a -> BS.Builder)
  toEncodedQueryParam :: Tagged b a -> Builder
toEncodedQueryParam = (a -> Builder) -> Tagged b a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)

-- | @since 0.4.2
instance ToHttpApiData a => ToHttpApiData (Const a b) where
  toUrlPiece :: Const a b -> Text
toUrlPiece        = (a -> Text) -> Const a b -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toHeader :: Const a b -> ByteString
toHeader          = (a -> ByteString) -> Const a b -> ByteString
forall a b. Coercible a b => a -> b
coerce (a -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toHeader :: a -> ByteString)
  toQueryParam :: Const a b -> Text
toQueryParam      = (a -> Text) -> Const a b -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam :: a -> Text)
  toEncodedUrlPiece :: Const a b -> Builder
toEncodedUrlPiece = (a -> Builder) -> Const a b -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece ::  a -> BS.Builder)
  toEncodedQueryParam :: Const a b -> Builder
toEncodedQueryParam = (a -> Builder) -> Const a b -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)

-- | @since 0.4.2
instance ToHttpApiData a => ToHttpApiData (Identity a) where
  toUrlPiece :: Identity a -> Text
toUrlPiece        = (a -> Text) -> Identity a -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toHeader :: Identity a -> ByteString
toHeader          = (a -> ByteString) -> Identity a -> ByteString
forall a b. Coercible a b => a -> b
coerce (a -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toHeader :: a -> ByteString)
  toQueryParam :: Identity a -> Text
toQueryParam      = (a -> Text) -> Identity a -> Text
forall a b. Coercible a b => a -> b
coerce (a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam :: a -> Text)
  toEncodedUrlPiece :: Identity a -> Builder
toEncodedUrlPiece = (a -> Builder) -> Identity a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece ::  a -> BS.Builder)
  toEncodedQueryParam :: Identity a -> Builder
toEncodedQueryParam = (a -> Builder) -> Identity a -> Builder
forall a b. Coercible a b => a -> b
coerce (a -> Builder
forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)

-- |
-- >>> parseUrlPiece "_" :: Either Text ()
-- Right ()
instance FromHttpApiData () where
  parseUrlPiece :: Text -> Either Text ()
parseUrlPiece Text
"_" = () -> Either Text ()
forall a. a -> Either Text a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
  parseUrlPiece Text
s   = Text -> Either Text ()
forall a. Text -> Either Text a
defaultParseError Text
s

instance FromHttpApiData Char where
  parseUrlPiece :: Text -> Either Text Char
parseUrlPiece Text
s =
    case Text -> Maybe (Char, Text)
T.uncons Text
s of
      Just (Char
c, Text
s') | Text -> Bool
T.null Text
s' -> Char -> Either Text Char
forall a. a -> Either Text a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Char
c
      Maybe (Char, Text)
_            -> Text -> Either Text Char
forall a. Text -> Either Text a
defaultParseError Text
s

-- |
-- >>> showVersion <$> parseUrlPiece "1.2.3"
-- Right "1.2.3"
instance FromHttpApiData Version where
  parseUrlPiece :: Text -> Either Text Version
parseUrlPiece Text
s =
    case [(Version, String)] -> [(Version, String)]
forall a. [a] -> [a]
reverse (ReadP Version -> ReadS Version
forall a. ReadP a -> ReadS a
readP_to_S ReadP Version
parseVersion (Text -> String
T.unpack Text
s)) of
      ((Version
x, String
""):[(Version, String)]
_) -> Version -> Either Text Version
forall a. a -> Either Text a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Version
x
      [(Version, String)]
_           -> Text -> Either Text Version
forall a. Text -> Either Text a
defaultParseError Text
s

-- | Parsing a @'Void'@ value is always an error, considering @'Void'@ as a data type with no constructors.
instance FromHttpApiData Void where
  parseUrlPiece :: Text -> Either Text Void
parseUrlPiece Text
_ = Text -> Either Text Void
forall a b. a -> Either a b
Left Text
"Void cannot be parsed!"

instance FromHttpApiData Natural where
  parseUrlPiece :: Text -> Either Text Natural
parseUrlPiece Text
s = do
    Integer
n <- Reader Integer -> Text -> Either Text Integer
forall a. Reader a -> Text -> Either Text a
runReader (Reader Integer -> Reader Integer
forall a. Num a => Reader a -> Reader a
signed Reader Integer
forall a. Integral a => Reader a
decimal) Text
s
    if Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0
      then Text -> Either Text Natural
forall a b. a -> Either a b
Left (Text
"underflow: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" (should be a non-negative integer)")
      else Natural -> Either Text Natural
forall a b. b -> Either a b
Right (Integer -> Natural
forall a. Num a => Integer -> a
fromInteger Integer
n)

instance FromHttpApiData Bool     where parseUrlPiece :: Text -> Either Text Bool
parseUrlPiece = Text -> Either Text Bool
forall a.
(ToHttpApiData a, Bounded a, Enum a) =>
Text -> Either Text a
parseBoundedUrlPiece
instance FromHttpApiData Ordering where parseUrlPiece :: Text -> Either Text Ordering
parseUrlPiece = Text -> Either Text Ordering
forall a.
(ToHttpApiData a, Bounded a, Enum a) =>
Text -> Either Text a
parseBoundedUrlPiece
instance FromHttpApiData Double   where parseUrlPiece :: Text -> Either Text Double
parseUrlPiece = Reader Double -> Text -> Either Text Double
forall a. Reader a -> Text -> Either Text a
runReader Reader Double
forall a. Fractional a => Reader a
rational
instance FromHttpApiData Float    where parseUrlPiece :: Text -> Either Text Float
parseUrlPiece = Reader Float -> Text -> Either Text Float
forall a. Reader a -> Text -> Either Text a
runReader Reader Float
forall a. Fractional a => Reader a
rational
instance FromHttpApiData Int      where parseUrlPiece :: Text -> Either Text Int
parseUrlPiece = Reader Integer -> Text -> Either Text Int
forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded (Reader Integer -> Reader Integer
forall a. Num a => Reader a -> Reader a
signed Reader Integer
forall a. Integral a => Reader a
decimal)
instance FromHttpApiData Int8     where parseUrlPiece :: Text -> Either Text Int8
parseUrlPiece = Reader Integer -> Text -> Either Text Int8
forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded (Reader Integer -> Reader Integer
forall a. Num a => Reader a -> Reader a
signed Reader Integer
forall a. Integral a => Reader a
decimal)
instance FromHttpApiData Int16    where parseUrlPiece :: Text -> Either Text Int16
parseUrlPiece = Reader Integer -> Text -> Either Text Int16
forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded (Reader Integer -> Reader Integer
forall a. Num a => Reader a -> Reader a
signed Reader Integer
forall a. Integral a => Reader a
decimal)
instance FromHttpApiData Int32    where parseUrlPiece :: Text -> Either Text Int32
parseUrlPiece = Reader Integer -> Text -> Either Text Int32
forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded (Reader Integer -> Reader Integer
forall a. Num a => Reader a -> Reader a
signed Reader Integer
forall a. Integral a => Reader a
decimal)
instance FromHttpApiData Int64    where parseUrlPiece :: Text -> Either Text Int64
parseUrlPiece = Reader Integer -> Text -> Either Text Int64
forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded (Reader Integer -> Reader Integer
forall a. Num a => Reader a -> Reader a
signed Reader Integer
forall a. Integral a => Reader a
decimal)
instance FromHttpApiData Integer  where parseUrlPiece :: Text -> Either Text Integer
parseUrlPiece = Reader Integer -> Text -> Either Text Integer
forall a. Reader a -> Text -> Either Text a
runReader (Reader Integer -> Reader Integer
forall a. Num a => Reader a -> Reader a
signed Reader Integer
forall a. Integral a => Reader a
decimal)
instance FromHttpApiData Word     where parseUrlPiece :: Text -> Either Text Word
parseUrlPiece = Reader Integer -> Text -> Either Text Word
forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded Reader Integer
forall a. Integral a => Reader a
decimal
instance FromHttpApiData Word8    where parseUrlPiece :: Text -> Either Text Word8
parseUrlPiece = Reader Integer -> Text -> Either Text Word8
forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded Reader Integer
forall a. Integral a => Reader a
decimal
instance FromHttpApiData Word16   where parseUrlPiece :: Text -> Either Text Word16
parseUrlPiece = Reader Integer -> Text -> Either Text Word16
forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded Reader Integer
forall a. Integral a => Reader a
decimal
instance FromHttpApiData Word32   where parseUrlPiece :: Text -> Either Text Word32
parseUrlPiece = Reader Integer -> Text -> Either Text Word32
forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded Reader Integer
forall a. Integral a => Reader a
decimal
instance FromHttpApiData Word64   where parseUrlPiece :: Text -> Either Text Word64
parseUrlPiece = Reader Integer -> Text -> Either Text Word64
forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded Reader Integer
forall a. Integral a => Reader a
decimal
instance FromHttpApiData String   where parseUrlPiece :: Text -> Either Text String
parseUrlPiece = String -> Either Text String
forall a b. b -> Either a b
Right (String -> Either Text String)
-> (Text -> String) -> Text -> Either Text String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
instance FromHttpApiData Text     where parseUrlPiece :: Text -> Either Text Text
parseUrlPiece = Text -> Either Text Text
forall a b. b -> Either a b
Right
instance FromHttpApiData L.Text   where parseUrlPiece :: Text -> Either Text Text
parseUrlPiece = Text -> Either Text Text
forall a b. b -> Either a b
Right (Text -> Either Text Text)
-> (Text -> Text) -> Text -> Either Text Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
L.fromStrict

-- | Note: this instance is not polykinded
instance F.HasResolution a => FromHttpApiData (F.Fixed (a :: Type)) where
    parseUrlPiece :: Text -> Either Text (Fixed a)
parseUrlPiece = Reader (Fixed a) -> Text -> Either Text (Fixed a)
forall a. Reader a -> Text -> Either Text a
runReader Reader (Fixed a)
forall a. Fractional a => Reader a
rational

-- |
-- >>> toGregorian <$> parseUrlPiece "2016-12-01"
-- Right (2016,12,1)
instance FromHttpApiData Day where parseUrlPiece :: Text -> Either Text Day
parseUrlPiece = (Text -> Either String Day) -> Text -> Either Text Day
forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String Day
FT.parseDay

-- |
-- >>> parseUrlPiece "14:55:01.333" :: Either Text TimeOfDay
-- Right 14:55:01.333
instance FromHttpApiData TimeOfDay where parseUrlPiece :: Text -> Either Text TimeOfDay
parseUrlPiece = (Text -> Either String TimeOfDay) -> Text -> Either Text TimeOfDay
forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String TimeOfDay
FT.parseTimeOfDay

-- |
-- >>> parseUrlPiece "2015-10-03T14:55:01" :: Either Text LocalTime
-- Right 2015-10-03 14:55:01
instance FromHttpApiData LocalTime where parseUrlPiece :: Text -> Either Text LocalTime
parseUrlPiece = (Text -> Either String LocalTime) -> Text -> Either Text LocalTime
forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String LocalTime
FT.parseLocalTime

-- |
-- >>> parseUrlPiece "2015-10-03T14:55:01+0000" :: Either Text ZonedTime
-- Right 2015-10-03 14:55:01 +0000
--
-- >>> parseQueryParam "2016-12-31T01:00:00Z" :: Either Text ZonedTime
-- Right 2016-12-31 01:00:00 +0000
instance FromHttpApiData ZonedTime where parseUrlPiece :: Text -> Either Text ZonedTime
parseUrlPiece = (Text -> Either String ZonedTime) -> Text -> Either Text ZonedTime
forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String ZonedTime
FT.parseZonedTime

-- |
-- >>> parseUrlPiece "2015-10-03T00:14:24Z" :: Either Text UTCTime
-- Right 2015-10-03 00:14:24 UTC
instance FromHttpApiData UTCTime   where parseUrlPiece :: Text -> Either Text UTCTime
parseUrlPiece = (Text -> Either String UTCTime) -> Text -> Either Text UTCTime
forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String UTCTime
FT.parseUTCTime

-- |
-- >>> parseUrlPiece "Monday" :: Either Text DayOfWeek
-- Right Monday
instance FromHttpApiData DayOfWeek where
  parseUrlPiece :: Text -> Either Text DayOfWeek
parseUrlPiece Text
t = case Text -> Map Text DayOfWeek -> Maybe DayOfWeek
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Text -> Text
T.toLower Text
t) Map Text DayOfWeek
m of
      Just DayOfWeek
dow -> DayOfWeek -> Either Text DayOfWeek
forall a b. b -> Either a b
Right DayOfWeek
dow
      Maybe DayOfWeek
Nothing  -> Text -> Either Text DayOfWeek
forall a b. a -> Either a b
Left (Text -> Either Text DayOfWeek) -> Text -> Either Text DayOfWeek
forall a b. (a -> b) -> a -> b
$ Text
"Incorrect DayOfWeek: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.take Int
10 Text
t
    where
      m :: Map.Map Text DayOfWeek
      m :: Map Text DayOfWeek
m = [(Text, DayOfWeek)] -> Map Text DayOfWeek
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [ (DayOfWeek -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece DayOfWeek
dow, DayOfWeek
dow) | DayOfWeek
dow <- [DayOfWeek
Monday .. DayOfWeek
Sunday] ]


instance FromHttpApiData NominalDiffTime where parseUrlPiece :: Text -> Either Text NominalDiffTime
parseUrlPiece = (Pico -> NominalDiffTime)
-> Either Text Pico -> Either Text NominalDiffTime
forall a b. (a -> b) -> Either Text a -> Either Text b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Pico -> NominalDiffTime
secondsToNominalDiffTime (Either Text Pico -> Either Text NominalDiffTime)
-> (Text -> Either Text Pico)
-> Text
-> Either Text NominalDiffTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text Pico
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece

-- |
-- >>> parseUrlPiece "2021-01" :: Either Text Month
-- Right 2021-01
instance FromHttpApiData Month where parseUrlPiece :: Text -> Either Text Month
parseUrlPiece = (Text -> Either String Month) -> Text -> Either Text Month
forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String Month
FT.parseMonth

-- |
-- >>> parseUrlPiece "2021-q1" :: Either Text Quarter
-- Right 2021-Q1
instance FromHttpApiData Quarter where parseUrlPiece :: Text -> Either Text Quarter
parseUrlPiece = (Text -> Either String Quarter) -> Text -> Either Text Quarter
forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String Quarter
FT.parseQuarter

-- |
-- >>> parseUrlPiece "q2" :: Either Text QuarterOfYear
-- Right Q2
--
-- >>> parseUrlPiece "Q3" :: Either Text QuarterOfYear
-- Right Q3
instance FromHttpApiData QuarterOfYear where parseUrlPiece :: Text -> Either Text QuarterOfYear
parseUrlPiece = (Text -> Either String QuarterOfYear)
-> Text -> Either Text QuarterOfYear
forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String QuarterOfYear
FT.parseQuarterOfYear

instance FromHttpApiData All where parseUrlPiece :: Text -> Either Text All
parseUrlPiece = (Text -> Either Text Bool) -> Text -> Either Text All
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text Bool
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text Bool)
instance FromHttpApiData Any where parseUrlPiece :: Text -> Either Text Any
parseUrlPiece = (Text -> Either Text Bool) -> Text -> Either Text Any
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text Bool
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text Bool)

instance FromHttpApiData a => FromHttpApiData (Dual a)    where parseUrlPiece :: Text -> Either Text (Dual a)
parseUrlPiece = (Text -> Either Text a) -> Text -> Either Text (Dual a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
instance FromHttpApiData a => FromHttpApiData (Sum a)     where parseUrlPiece :: Text -> Either Text (Sum a)
parseUrlPiece = (Text -> Either Text a) -> Text -> Either Text (Sum a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
instance FromHttpApiData a => FromHttpApiData (Product a) where parseUrlPiece :: Text -> Either Text (Product a)
parseUrlPiece = (Text -> Either Text a) -> Text -> Either Text (Product a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
instance FromHttpApiData a => FromHttpApiData (First a)   where parseUrlPiece :: Text -> Either Text (First a)
parseUrlPiece = (Text -> Either Text (Maybe a)) -> Text -> Either Text (First a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text (Maybe a)
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text (Maybe a))
instance FromHttpApiData a => FromHttpApiData (Last a)    where parseUrlPiece :: Text -> Either Text (Last a)
parseUrlPiece = (Text -> Either Text (Maybe a)) -> Text -> Either Text (Last a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text (Maybe a)
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text (Maybe a))

instance FromHttpApiData a => FromHttpApiData (Semi.Min a)    where parseUrlPiece :: Text -> Either Text (Min a)
parseUrlPiece = (Text -> Either Text a) -> Text -> Either Text (Min a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
instance FromHttpApiData a => FromHttpApiData (Semi.Max a)    where parseUrlPiece :: Text -> Either Text (Max a)
parseUrlPiece = (Text -> Either Text a) -> Text -> Either Text (Max a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
instance FromHttpApiData a => FromHttpApiData (Semi.First a)  where parseUrlPiece :: Text -> Either Text (First a)
parseUrlPiece = (Text -> Either Text a) -> Text -> Either Text (First a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
instance FromHttpApiData a => FromHttpApiData (Semi.Last a)   where parseUrlPiece :: Text -> Either Text (Last a)
parseUrlPiece = (Text -> Either Text a) -> Text -> Either Text (Last a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)

-- |
-- >>> parseUrlPiece "Just 123" :: Either Text (Maybe Int)
-- Right (Just 123)
instance FromHttpApiData a => FromHttpApiData (Maybe a) where
  parseUrlPiece :: Text -> Either Text (Maybe a)
parseUrlPiece Text
s
    | Text -> Text
T.toLower (Int -> Text -> Text
T.take Int
7 Text
s) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"nothing" = Maybe a -> Either Text (Maybe a)
forall a. a -> Either Text a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
    | Bool
otherwise                           = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> Either Text a -> Either Text (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> Either Text a
forall a. FromHttpApiData a => Text -> Text -> Either Text a
parseUrlPieceWithPrefix Text
"Just " Text
s

-- |
-- >>> parseUrlPiece "Right 123" :: Either Text (Either String Int)
-- Right (Right 123)
instance (FromHttpApiData a, FromHttpApiData b) => FromHttpApiData (Either a b) where
  parseUrlPiece :: Text -> Either Text (Either a b)
parseUrlPiece Text
s =
        b -> Either a b
forall a b. b -> Either a b
Right (b -> Either a b) -> Either Text b -> Either Text (Either a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> Either Text b
forall a. FromHttpApiData a => Text -> Text -> Either Text a
parseUrlPieceWithPrefix Text
"Right " Text
s
    Either Text (Either a b)
-> Either Text (Either a b) -> Either Text (Either a b)
forall {a} {b}. Either a b -> Either a b -> Either a b
<!> a -> Either a b
forall a b. a -> Either a b
Left  (a -> Either a b) -> Either Text a -> Either Text (Either a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> Either Text a
forall a. FromHttpApiData a => Text -> Text -> Either Text a
parseUrlPieceWithPrefix Text
"Left " Text
s
    where
      infixl 3 <!>
      Left a
_ <!> :: Either a b -> Either a b -> Either a b
<!> Either a b
y = Either a b
y
      Either a b
x      <!> Either a b
_ = Either a b
x

instance ToHttpApiData UUID.UUID where
    toUrlPiece :: UUID -> Text
toUrlPiece = UUID -> Text
UUID.toText
    toHeader :: UUID -> ByteString
toHeader   = UUID -> ByteString
UUID.toASCIIBytes
    toEncodedUrlPiece :: UUID -> Builder
toEncodedUrlPiece = UUID -> Builder
forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece

instance FromHttpApiData UUID.UUID where
    parseUrlPiece :: Text -> Either Text UUID
parseUrlPiece = Either Text UUID
-> (UUID -> Either Text UUID) -> Maybe UUID -> Either Text UUID
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Text -> Either Text UUID
forall a b. a -> Either a b
Left Text
"invalid UUID") UUID -> Either Text UUID
forall a b. b -> Either a b
Right (Maybe UUID -> Either Text UUID)
-> (Text -> Maybe UUID) -> Text -> Either Text UUID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe UUID
UUID.fromText
    parseHeader :: ByteString -> Either Text UUID
parseHeader   = Either Text UUID
-> (UUID -> Either Text UUID) -> Maybe UUID -> Either Text UUID
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Text -> Either Text UUID
forall a b. a -> Either a b
Left Text
"invalid UUID") UUID -> Either Text UUID
forall a b. b -> Either a b
Right (Maybe UUID -> Either Text UUID)
-> (ByteString -> Maybe UUID) -> ByteString -> Either Text UUID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe UUID
UUID.fromASCIIBytes


-- | Lenient parameters. 'FromHttpApiData' combinators always return `Right`.
--
-- @since 0.3.5
newtype LenientData a = LenientData { forall a. LenientData a -> Either Text a
getLenientData :: Either Text a }
    deriving (LenientData a -> LenientData a -> Bool
(LenientData a -> LenientData a -> Bool)
-> (LenientData a -> LenientData a -> Bool) -> Eq (LenientData a)
forall a. Eq a => LenientData a -> LenientData a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => LenientData a -> LenientData a -> Bool
== :: LenientData a -> LenientData a -> Bool
$c/= :: forall a. Eq a => LenientData a -> LenientData a -> Bool
/= :: LenientData a -> LenientData a -> Bool
Eq, Eq (LenientData a)
Eq (LenientData a) =>
(LenientData a -> LenientData a -> Ordering)
-> (LenientData a -> LenientData a -> Bool)
-> (LenientData a -> LenientData a -> Bool)
-> (LenientData a -> LenientData a -> Bool)
-> (LenientData a -> LenientData a -> Bool)
-> (LenientData a -> LenientData a -> LenientData a)
-> (LenientData a -> LenientData a -> LenientData a)
-> Ord (LenientData a)
LenientData a -> LenientData a -> Bool
LenientData a -> LenientData a -> Ordering
LenientData a -> LenientData a -> LenientData a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (LenientData a)
forall a. Ord a => LenientData a -> LenientData a -> Bool
forall a. Ord a => LenientData a -> LenientData a -> Ordering
forall a. Ord a => LenientData a -> LenientData a -> LenientData a
$ccompare :: forall a. Ord a => LenientData a -> LenientData a -> Ordering
compare :: LenientData a -> LenientData a -> Ordering
$c< :: forall a. Ord a => LenientData a -> LenientData a -> Bool
< :: LenientData a -> LenientData a -> Bool
$c<= :: forall a. Ord a => LenientData a -> LenientData a -> Bool
<= :: LenientData a -> LenientData a -> Bool
$c> :: forall a. Ord a => LenientData a -> LenientData a -> Bool
> :: LenientData a -> LenientData a -> Bool
$c>= :: forall a. Ord a => LenientData a -> LenientData a -> Bool
>= :: LenientData a -> LenientData a -> Bool
$cmax :: forall a. Ord a => LenientData a -> LenientData a -> LenientData a
max :: LenientData a -> LenientData a -> LenientData a
$cmin :: forall a. Ord a => LenientData a -> LenientData a -> LenientData a
min :: LenientData a -> LenientData a -> LenientData a
Ord, Int -> LenientData a -> ShowS
[LenientData a] -> ShowS
LenientData a -> String
(Int -> LenientData a -> ShowS)
-> (LenientData a -> String)
-> ([LenientData a] -> ShowS)
-> Show (LenientData a)
forall a. Show a => Int -> LenientData a -> ShowS
forall a. Show a => [LenientData a] -> ShowS
forall a. Show a => LenientData a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> LenientData a -> ShowS
showsPrec :: Int -> LenientData a -> ShowS
$cshow :: forall a. Show a => LenientData a -> String
show :: LenientData a -> String
$cshowList :: forall a. Show a => [LenientData a] -> ShowS
showList :: [LenientData a] -> ShowS
Show, ReadPrec [LenientData a]
ReadPrec (LenientData a)
Int -> ReadS (LenientData a)
ReadS [LenientData a]
(Int -> ReadS (LenientData a))
-> ReadS [LenientData a]
-> ReadPrec (LenientData a)
-> ReadPrec [LenientData a]
-> Read (LenientData a)
forall a. Read a => ReadPrec [LenientData a]
forall a. Read a => ReadPrec (LenientData a)
forall a. Read a => Int -> ReadS (LenientData a)
forall a. Read a => ReadS [LenientData a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall a. Read a => Int -> ReadS (LenientData a)
readsPrec :: Int -> ReadS (LenientData a)
$creadList :: forall a. Read a => ReadS [LenientData a]
readList :: ReadS [LenientData a]
$creadPrec :: forall a. Read a => ReadPrec (LenientData a)
readPrec :: ReadPrec (LenientData a)
$creadListPrec :: forall a. Read a => ReadPrec [LenientData a]
readListPrec :: ReadPrec [LenientData a]
Read, Typeable, Typeable (LenientData a)
Typeable (LenientData a) =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> LenientData a -> c (LenientData a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (LenientData a))
-> (LenientData a -> Constr)
-> (LenientData a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (LenientData a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (LenientData a)))
-> ((forall b. Data b => b -> b) -> LenientData a -> LenientData a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> LenientData a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> LenientData a -> r)
-> (forall u. (forall d. Data d => d -> u) -> LenientData a -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> LenientData a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> LenientData a -> m (LenientData a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> LenientData a -> m (LenientData a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> LenientData a -> m (LenientData a))
-> Data (LenientData a)
LenientData a -> Constr
LenientData a -> DataType
(forall b. Data b => b -> b) -> LenientData a -> LenientData a
forall a. Data a => Typeable (LenientData a)
forall a. Data a => LenientData a -> Constr
forall a. Data a => LenientData a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> LenientData a -> LenientData a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> LenientData a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> LenientData a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LenientData a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LenientData a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> LenientData a -> m (LenientData a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> LenientData a -> m (LenientData a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (LenientData a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LenientData a -> c (LenientData a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (LenientData a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (LenientData a))
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> LenientData a -> u
forall u. (forall d. Data d => d -> u) -> LenientData a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LenientData a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LenientData a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> LenientData a -> m (LenientData a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LenientData a -> m (LenientData a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (LenientData a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LenientData a -> c (LenientData a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (LenientData a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (LenientData a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LenientData a -> c (LenientData a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LenientData a -> c (LenientData a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (LenientData a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (LenientData a)
$ctoConstr :: forall a. Data a => LenientData a -> Constr
toConstr :: LenientData a -> Constr
$cdataTypeOf :: forall a. Data a => LenientData a -> DataType
dataTypeOf :: LenientData a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (LenientData a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (LenientData a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (LenientData a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (LenientData a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> LenientData a -> LenientData a
gmapT :: (forall b. Data b => b -> b) -> LenientData a -> LenientData a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LenientData a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LenientData a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LenientData a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LenientData a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> LenientData a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> LenientData a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> LenientData a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LenientData a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> LenientData a -> m (LenientData a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> LenientData a -> m (LenientData a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> LenientData a -> m (LenientData a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LenientData a -> m (LenientData a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> LenientData a -> m (LenientData a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> LenientData a -> m (LenientData a)
Data, (forall a b. (a -> b) -> LenientData a -> LenientData b)
-> (forall a b. a -> LenientData b -> LenientData a)
-> Functor LenientData
forall a b. a -> LenientData b -> LenientData a
forall a b. (a -> b) -> LenientData a -> LenientData b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> LenientData a -> LenientData b
fmap :: forall a b. (a -> b) -> LenientData a -> LenientData b
$c<$ :: forall a b. a -> LenientData b -> LenientData a
<$ :: forall a b. a -> LenientData b -> LenientData a
Functor, (forall m. Monoid m => LenientData m -> m)
-> (forall m a. Monoid m => (a -> m) -> LenientData a -> m)
-> (forall m a. Monoid m => (a -> m) -> LenientData a -> m)
-> (forall a b. (a -> b -> b) -> b -> LenientData a -> b)
-> (forall a b. (a -> b -> b) -> b -> LenientData a -> b)
-> (forall b a. (b -> a -> b) -> b -> LenientData a -> b)
-> (forall b a. (b -> a -> b) -> b -> LenientData a -> b)
-> (forall a. (a -> a -> a) -> LenientData a -> a)
-> (forall a. (a -> a -> a) -> LenientData a -> a)
-> (forall a. LenientData a -> [a])
-> (forall a. LenientData a -> Bool)
-> (forall a. LenientData a -> Int)
-> (forall a. Eq a => a -> LenientData a -> Bool)
-> (forall a. Ord a => LenientData a -> a)
-> (forall a. Ord a => LenientData a -> a)
-> (forall a. Num a => LenientData a -> a)
-> (forall a. Num a => LenientData a -> a)
-> Foldable LenientData
forall a. Eq a => a -> LenientData a -> Bool
forall a. Num a => LenientData a -> a
forall a. Ord a => LenientData a -> a
forall m. Monoid m => LenientData m -> m
forall a. LenientData a -> Bool
forall a. LenientData a -> Int
forall a. LenientData a -> [a]
forall a. (a -> a -> a) -> LenientData a -> a
forall m a. Monoid m => (a -> m) -> LenientData a -> m
forall b a. (b -> a -> b) -> b -> LenientData a -> b
forall a b. (a -> b -> b) -> b -> LenientData a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => LenientData m -> m
fold :: forall m. Monoid m => LenientData m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> LenientData a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> LenientData a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> LenientData a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> LenientData a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> LenientData a -> b
foldr :: forall a b. (a -> b -> b) -> b -> LenientData a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> LenientData a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> LenientData a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> LenientData a -> b
foldl :: forall b a. (b -> a -> b) -> b -> LenientData a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> LenientData a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> LenientData a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> LenientData a -> a
foldr1 :: forall a. (a -> a -> a) -> LenientData a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> LenientData a -> a
foldl1 :: forall a. (a -> a -> a) -> LenientData a -> a
$ctoList :: forall a. LenientData a -> [a]
toList :: forall a. LenientData a -> [a]
$cnull :: forall a. LenientData a -> Bool
null :: forall a. LenientData a -> Bool
$clength :: forall a. LenientData a -> Int
length :: forall a. LenientData a -> Int
$celem :: forall a. Eq a => a -> LenientData a -> Bool
elem :: forall a. Eq a => a -> LenientData a -> Bool
$cmaximum :: forall a. Ord a => LenientData a -> a
maximum :: forall a. Ord a => LenientData a -> a
$cminimum :: forall a. Ord a => LenientData a -> a
minimum :: forall a. Ord a => LenientData a -> a
$csum :: forall a. Num a => LenientData a -> a
sum :: forall a. Num a => LenientData a -> a
$cproduct :: forall a. Num a => LenientData a -> a
product :: forall a. Num a => LenientData a -> a
Foldable, Functor LenientData
Foldable LenientData
(Functor LenientData, Foldable LenientData) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> LenientData a -> f (LenientData b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    LenientData (f a) -> f (LenientData a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> LenientData a -> m (LenientData b))
-> (forall (m :: * -> *) a.
    Monad m =>
    LenientData (m a) -> m (LenientData a))
-> Traversable LenientData
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
LenientData (m a) -> m (LenientData a)
forall (f :: * -> *) a.
Applicative f =>
LenientData (f a) -> f (LenientData a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> LenientData a -> m (LenientData b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> LenientData a -> f (LenientData b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> LenientData a -> f (LenientData b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> LenientData a -> f (LenientData b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
LenientData (f a) -> f (LenientData a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
LenientData (f a) -> f (LenientData a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> LenientData a -> m (LenientData b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> LenientData a -> m (LenientData b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
LenientData (m a) -> m (LenientData a)
sequence :: forall (m :: * -> *) a.
Monad m =>
LenientData (m a) -> m (LenientData a)
Traversable)

instance FromHttpApiData a => FromHttpApiData (LenientData a) where
    parseUrlPiece :: Text -> Either Text (LenientData a)
parseUrlPiece   = LenientData a -> Either Text (LenientData a)
forall a b. b -> Either a b
Right (LenientData a -> Either Text (LenientData a))
-> (Text -> LenientData a) -> Text -> Either Text (LenientData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Text a -> LenientData a
forall a. Either Text a -> LenientData a
LenientData (Either Text a -> LenientData a)
-> (Text -> Either Text a) -> Text -> LenientData a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece
    parseHeader :: ByteString -> Either Text (LenientData a)
parseHeader     = LenientData a -> Either Text (LenientData a)
forall a b. b -> Either a b
Right (LenientData a -> Either Text (LenientData a))
-> (ByteString -> LenientData a)
-> ByteString
-> Either Text (LenientData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Text a -> LenientData a
forall a. Either Text a -> LenientData a
LenientData (Either Text a -> LenientData a)
-> (ByteString -> Either Text a) -> ByteString -> LenientData a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either Text a
forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader
    parseQueryParam :: Text -> Either Text (LenientData a)
parseQueryParam = LenientData a -> Either Text (LenientData a)
forall a b. b -> Either a b
Right (LenientData a -> Either Text (LenientData a))
-> (Text -> LenientData a) -> Text -> Either Text (LenientData a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Text a -> LenientData a
forall a. Either Text a -> LenientData a
LenientData (Either Text a -> LenientData a)
-> (Text -> Either Text a) -> Text -> LenientData a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam

-- | /Note:/ this instance works correctly for alphanumeric name and value
--
-- >>> parseUrlPiece "SESSID=r2t5uvjq435r4q7ib3vtdjq120" :: Either Text SetCookie
-- Right (SetCookie {setCookieName = "SESSID", setCookieValue = "r2t5uvjq435r4q7ib3vtdjq120", setCookiePath = Nothing, setCookieExpires = Nothing, setCookieMaxAge = Nothing, setCookieDomain = Nothing, setCookieHttpOnly = False, setCookieSecure = False, setCookieSameSite = Nothing})
instance FromHttpApiData SetCookie where
  parseUrlPiece :: Text -> Either Text SetCookie
parseUrlPiece = ByteString -> Either Text SetCookie
forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader  (ByteString -> Either Text SetCookie)
-> (Text -> ByteString) -> Text -> Either Text SetCookie
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8
  parseHeader :: ByteString -> Either Text SetCookie
parseHeader   = SetCookie -> Either Text SetCookie
forall a b. b -> Either a b
Right (SetCookie -> Either Text SetCookie)
-> (ByteString -> SetCookie) -> ByteString -> Either Text SetCookie
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> SetCookie
parseSetCookie

-- | Note: this instance is not polykinded
instance FromHttpApiData a => FromHttpApiData (Tagged (b :: Type) a) where
  parseUrlPiece :: Text -> Either Text (Tagged b a)
parseUrlPiece   = (Text -> Either Text a) -> Text -> Either Text (Tagged b a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
  parseHeader :: ByteString -> Either Text (Tagged b a)
parseHeader     = (ByteString -> Either Text a)
-> ByteString -> Either Text (Tagged b a)
forall a b. Coercible a b => a -> b
coerce (ByteString -> Either Text a
forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader :: ByteString -> Either Text a)
  parseQueryParam :: Text -> Either Text (Tagged b a)
parseQueryParam = (Text -> Either Text a) -> Text -> Either Text (Tagged b a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam :: Text -> Either Text a)

-- | @since 0.4.2
instance FromHttpApiData a => FromHttpApiData (Const a b) where
  parseUrlPiece :: Text -> Either Text (Const a b)
parseUrlPiece   = (Text -> Either Text a) -> Text -> Either Text (Const a b)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
  parseHeader :: ByteString -> Either Text (Const a b)
parseHeader     = (ByteString -> Either Text a)
-> ByteString -> Either Text (Const a b)
forall a b. Coercible a b => a -> b
coerce (ByteString -> Either Text a
forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader :: ByteString -> Either Text a)
  parseQueryParam :: Text -> Either Text (Const a b)
parseQueryParam = (Text -> Either Text a) -> Text -> Either Text (Const a b)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam :: Text -> Either Text a)

-- | @since 0.4.2
instance FromHttpApiData a => FromHttpApiData (Identity a) where
  parseUrlPiece :: Text -> Either Text (Identity a)
parseUrlPiece   = (Text -> Either Text a) -> Text -> Either Text (Identity a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
  parseHeader :: ByteString -> Either Text (Identity a)
parseHeader     = (ByteString -> Either Text a)
-> ByteString -> Either Text (Identity a)
forall a b. Coercible a b => a -> b
coerce (ByteString -> Either Text a
forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader :: ByteString -> Either Text a)
  parseQueryParam :: Text -> Either Text (Identity a)
parseQueryParam = (Text -> Either Text a) -> Text -> Either Text (Identity a)
forall a b. Coercible a b => a -> b
coerce (Text -> Either Text a
forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam :: Text -> Either Text a)

-------------------------------------------------------------------------------
-- Helpers
-------------------------------------------------------------------------------

runTT :: (a -> Builder) -> a -> Text
runTT :: forall a. (a -> Builder) -> a -> Text
runTT a -> Builder
f a
x = Text -> Text
L.toStrict (Builder -> Text
toLazyText (a -> Builder
f a
x))

runFT :: (Text -> Either String a) -> Text -> Either Text a
runFT :: forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String a
f Text
t = case Text -> Either String a
f Text
t of
    Left String
err -> Text -> Either Text a
forall a b. a -> Either a b
Left (String -> Text
T.pack String
err)
    Right a
x  -> a -> Either Text a
forall a b. b -> Either a b
Right a
x