{-# LANGUAGE CPP                  #-}
{-# LANGUAGE DefaultSignatures    #-}
{-# LANGUAGE DeriveDataTypeable   #-}
{-# LANGUAGE DeriveFoldable       #-}
{-# LANGUAGE DeriveFunctor        #-}
{-# LANGUAGE DeriveTraversable    #-}
{-# LANGUAGE FlexibleInstances    #-}
{-# LANGUAGE KindSignatures       #-}
{-# LANGUAGE OverloadedStrings    #-}
{-# LANGUAGE PolyKinds            #-}
{-# LANGUAGE ScopedTypeVariables  #-}
{-# LANGUAGE TypeSynonymInstances #-}
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
class ToHttpApiData a where
  {-# MINIMAL toUrlPiece | toQueryParam #-}
  
  toUrlPiece :: a -> Text
  toUrlPiece = forall a. ToHttpApiData a => a -> Text
toQueryParam
  
  
  
  toEncodedUrlPiece :: a -> BS.Builder
  toEncodedUrlPiece = Bool -> ByteString -> Builder
H.urlEncodeBuilder Bool
False forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToHttpApiData a => a -> Text
toUrlPiece
  
   :: a -> ByteString
  toHeader = Text -> ByteString
encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToHttpApiData a => a -> Text
toUrlPiece
  
  toQueryParam :: a -> Text
  toQueryParam = forall a. ToHttpApiData a => a -> Text
toUrlPiece
  
  
  
  
  
  toEncodedQueryParam :: a -> BS.Builder
  toEncodedQueryParam = Bool -> ByteString -> Builder
H.urlEncodeBuilder Bool
True forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToHttpApiData a => a -> Text
toQueryParam
class FromHttpApiData a where
  {-# MINIMAL parseUrlPiece | parseQueryParam #-}
  
  parseUrlPiece :: Text -> Either Text a
  parseUrlPiece = forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam
  
   :: ByteString -> Either Text a
  parseHeader = forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either b d) (Either c d)
left (String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either UnicodeException Text
decodeUtf8')
  
  parseQueryParam :: Text -> Either Text a
  parseQueryParam = forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece
toUrlPieces :: (Functor t, ToHttpApiData a) => t a -> t Text
toUrlPieces :: forall (t :: * -> *) a.
(Functor t, ToHttpApiData a) =>
t a -> t Text
toUrlPieces = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. ToHttpApiData a => a -> Text
toUrlPiece
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 = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece
toQueryParams :: (Functor t, ToHttpApiData a) => t a -> t Text
toQueryParams :: forall (t :: * -> *) a.
(Functor t, ToHttpApiData a) =>
t a -> t Text
toQueryParams = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. ToHttpApiData a => a -> Text
toQueryParam
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 = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam
parseUrlPieceMaybe :: FromHttpApiData a => Text -> Maybe a
parseUrlPieceMaybe :: forall a. FromHttpApiData a => Text -> Maybe a
parseUrlPieceMaybe = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece
parseHeaderMaybe :: FromHttpApiData a => ByteString -> Maybe a
 = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader
parseQueryParamMaybe :: FromHttpApiData a => Text -> Maybe a
parseQueryParamMaybe :: forall a. FromHttpApiData a => Text -> Maybe a
parseQueryParamMaybe = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam
defaultParseError :: Text -> Either Text a
defaultParseError :: forall a. Text -> Either Text a
defaultParseError Text
input = forall a b. a -> Either a b
Left (Text
"could not parse: `" forall a. Semigroup a => a -> a -> a
<> Text
input forall a. Semigroup a => a -> a -> a
<> Text
"'")
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  -> forall a. Text -> Either Text a
defaultParseError Text
input
    Just a
val -> forall a b. b -> Either a b
Right a
val
#if USE_TEXT_SHOW
showTextData :: TextShow a => a -> Text
showTextData = T.toLower . showt
#else
showTextData :: Show a => a -> Text
showTextData :: forall a. Show a => a -> Text
showTextData = Text -> Text
T.toLower forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> Text
showt
showt :: Show a => a -> Text
showt :: forall a. Show a => a -> Text
showt = String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
#endif
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 forall a. Eq a => a -> a -> Bool
== Text -> Text
T.toLower Text
prefix = forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece Text
rest
  | Bool
otherwise                             = 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
parseHeaderWithPrefix :: FromHttpApiData a => ByteString -> ByteString -> Either Text a
 ByteString
pattern ByteString
input
  | ByteString
pattern ByteString -> ByteString -> Bool
`BS.isPrefixOf` ByteString
input = forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader (Int -> ByteString -> ByteString
BS.drop (ByteString -> Int
BS.length ByteString
pattern) ByteString
input)
  | Bool
otherwise                     = forall a. Text -> Either Text a
defaultParseError (forall a. Show a => a -> Text
showt ByteString
input)
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 forall a. Eq a => a -> a -> Bool
== Text -> Text
T.toLower Text
prefix = forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam Text
rest
  | Bool
otherwise                             = 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
parseBoundedTextData :: (TextShow a, Bounded a, Enum a) => Text -> Either Text a
#else
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 = forall a.
(Bounded a, Enum a) =>
(a -> Text) -> Text -> Either Text a
parseBoundedEnumOfI forall a. Show a => a -> Text
showTextData
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 = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (forall a b. (a -> b) -> [a] -> [b]
map (a -> b
f forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& forall a. a -> a
id) [forall a. Bounded a => a
minBound..forall a. Bounded a => a
maxBound])
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 = forall a. (Text -> Maybe a) -> Text -> Either Text a
parseMaybeTextData forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Bounded a, Enum a, Eq b) => (a -> b) -> b -> Maybe a
lookupBoundedEnumOf
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 = forall a.
(Bounded a, Enum a) =>
(a -> Text) -> Text -> Either Text a
parseBoundedEnumOf (Text -> Text
T.toLower forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.toLower
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 = forall a.
(Bounded a, Enum a) =>
(a -> Text) -> Text -> Either Text a
parseBoundedEnumOfI forall a. ToHttpApiData a => a -> Text
toUrlPiece
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 = forall a.
(Bounded a, Enum a) =>
(a -> Text) -> Text -> Either Text a
parseBoundedEnumOfI forall a. ToHttpApiData a => a -> Text
toQueryParam
parseBoundedHeader :: (ToHttpApiData a, Bounded a, Enum a) => ByteString -> Either Text a
 ByteString
bs = case forall a b. (Bounded a, Enum a, Eq b) => (a -> b) -> b -> Maybe a
lookupBoundedEnumOf forall a. ToHttpApiData a => a -> ByteString
toHeader ByteString
bs of
  Maybe a
Nothing -> forall a. Text -> Either Text a
defaultParseError forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show ByteString
bs
  Just a
x  -> forall (m :: * -> *) a. Monad m => a -> m a
return a
x
readTextData :: Read a => Text -> Either Text a
readTextData :: forall a. Read a => Text -> Either Text a
readTextData = forall a. (Text -> Maybe a) -> Text -> Either Text a
parseMaybeTextData (forall a. Read a => String -> Maybe a
readMaybe forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack)
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          -> forall a b. a -> Either a b
Left (Text
"could not parse: `" forall a. Semigroup a => a -> a -> a
<> Text
input forall a. Semigroup a => a -> a -> a
<> Text
"' (" forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
err forall a. Semigroup a => a -> a -> a
<> Text
")")
    Right (a
x, Text
rest)
      | Text -> Bool
T.null Text
rest -> forall a b. b -> Either a b
Right a
x
      | Bool
otherwise   -> forall a. Text -> Either Text a
defaultParseError Text
input
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 <- forall a. Reader a -> Text -> Either Text a
runReader Reader Integer
reader Text
input
  if (Integer
n forall a. Ord a => a -> a -> Bool
> Integer
h Bool -> Bool -> Bool
|| Integer
n forall a. Ord a => a -> a -> Bool
< Integer
l)
    then forall a b. a -> Either a b
Left  (Text
"out of bounds: `" forall a. Semigroup a => a -> a -> a
<> Text
input forall a. Semigroup a => a -> a -> a
<> Text
"' (should be between " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> Text
showt Integer
l forall a. Semigroup a => a -> a -> a
<> Text
" and " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> Text
showt Integer
h forall a. Semigroup a => a -> a -> a
<> Text
")")
    else forall a b. b -> Either a b
Right (forall a. Num a => Integer -> a
fromInteger Integer
n)
  where
    l :: Integer
l = forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound :: a)
    h :: Integer
h = forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: a)
unsafeToEncodedUrlPiece :: ToHttpApiData a => a -> BS.Builder
unsafeToEncodedUrlPiece :: forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece = ByteString -> Builder
BS.byteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToHttpApiData a => a -> Text
toUrlPiece
unsafeToEncodedQueryParam :: ToHttpApiData a => a -> BS.Builder
unsafeToEncodedQueryParam :: forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam = ByteString -> Builder
BS.byteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToHttpApiData a => a -> Text
toQueryParam
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
instance ToHttpApiData Version where
  toUrlPiece :: Version -> Text
toUrlPiece = String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> String
showVersion
  toEncodedUrlPiece :: Version -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  toEncodedQueryParam :: Version -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Void    where toUrlPiece :: Void -> Text
toUrlPiece = forall a. Void -> a
absurd
instance ToHttpApiData Natural where toUrlPiece :: Natural -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Natural -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Natural -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Bool     where toUrlPiece :: Bool -> Text
toUrlPiece = forall a. Show a => a -> Text
showTextData; toEncodedUrlPiece :: Bool -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Bool -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Ordering where toUrlPiece :: Ordering -> Text
toUrlPiece = forall a. Show a => a -> Text
showTextData; toEncodedUrlPiece :: Ordering -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Ordering -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Double   where toUrlPiece :: Double -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Double -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Double -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Float    where toUrlPiece :: Float -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Float -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Float -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Int      where toUrlPiece :: Int -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Int -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Int -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Int8     where toUrlPiece :: Int8 -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Int8 -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Int8 -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Int16    where toUrlPiece :: Int16 -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Int16 -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Int16 -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Int32    where toUrlPiece :: Int32 -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Int32 -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Int32 -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Int64    where toUrlPiece :: Int64 -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Int64 -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Int64 -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Integer  where toUrlPiece :: Integer -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Integer -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Integer -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Word     where toUrlPiece :: Word -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Word -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Word -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Word8    where toUrlPiece :: Word8 -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Word8 -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Word8 -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Word16   where toUrlPiece :: Word16 -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Word16 -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Word16 -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Word32   where toUrlPiece :: Word32 -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Word32 -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Word32 -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Word64   where toUrlPiece :: Word64 -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Word64 -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Word64 -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance F.HasResolution a => ToHttpApiData (F.Fixed (a :: Type)) where toUrlPiece :: Fixed a -> Text
toUrlPiece = forall a. Show a => a -> Text
showt; toEncodedUrlPiece :: Fixed a -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece; toEncodedQueryParam :: Fixed a -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Day where
  toUrlPiece :: Day -> Text
toUrlPiece = forall a. (a -> Builder) -> a -> Text
runTT Day -> Builder
TT.buildDay
  toEncodedUrlPiece :: Day -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  toEncodedQueryParam :: Day -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData TimeOfDay where
  toUrlPiece :: TimeOfDay -> Text
toUrlPiece = forall a. (a -> Builder) -> a -> Text
runTT TimeOfDay -> Builder
TT.buildTimeOfDay
  toEncodedUrlPiece :: TimeOfDay -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  
instance ToHttpApiData LocalTime where
  toUrlPiece :: LocalTime -> Text
toUrlPiece = forall a. (a -> Builder) -> a -> Text
runTT LocalTime -> Builder
TT.buildLocalTime
  toEncodedUrlPiece :: LocalTime -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  
instance ToHttpApiData ZonedTime where
  toUrlPiece :: ZonedTime -> Text
toUrlPiece = forall a. (a -> Builder) -> a -> Text
runTT ZonedTime -> Builder
TT.buildZonedTime
  toEncodedUrlPiece :: ZonedTime -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  
instance ToHttpApiData UTCTime where
  toUrlPiece :: UTCTime -> Text
toUrlPiece = forall a. (a -> Builder) -> a -> Text
runTT UTCTime -> Builder
TT.buildUTCTime
  toEncodedUrlPiece :: UTCTime -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  
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 = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  toEncodedQueryParam :: DayOfWeek -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData QuarterOfYear where
  toUrlPiece :: QuarterOfYear -> Text
toUrlPiece = forall a. (a -> Builder) -> a -> Text
runTT QuarterOfYear -> Builder
TT.buildQuarterOfYear
  toEncodedUrlPiece :: QuarterOfYear -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  toEncodedQueryParam :: QuarterOfYear -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Quarter where
  toUrlPiece :: Quarter -> Text
toUrlPiece = forall a. (a -> Builder) -> a -> Text
runTT Quarter -> Builder
TT.buildQuarter
  toEncodedUrlPiece :: Quarter -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  toEncodedQueryParam :: Quarter -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData Month where
  toUrlPiece :: Month -> Text
toUrlPiece = forall a. (a -> Builder) -> a -> Text
runTT Month -> Builder
TT.buildMonth
  toEncodedUrlPiece :: Month -> Builder
toEncodedUrlPiece = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
  toEncodedQueryParam :: Month -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
instance ToHttpApiData NominalDiffTime where
  toUrlPiece :: NominalDiffTime -> Text
toUrlPiece = forall a. ToHttpApiData a => a -> Text
toUrlPiece forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTime -> Pico
nominalDiffTimeToSeconds
  toEncodedQueryParam :: NominalDiffTime -> Builder
toEncodedQueryParam = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedQueryParam
  toEncodedUrlPiece :: NominalDiffTime -> Builder
toEncodedUrlPiece = 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 = 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        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: Bool -> Text)
  toEncodedUrlPiece :: All -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: Bool -> BS.Builder)
  toEncodedQueryParam :: All -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: Bool -> BS.Builder)
instance ToHttpApiData Any where
  toUrlPiece :: Any -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: Bool -> Text)
  toEncodedUrlPiece :: Any -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: Bool -> BS.Builder)
  toEncodedQueryParam :: Any -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: Bool -> BS.Builder)
instance ToHttpApiData a => ToHttpApiData (Dual a) where
  toUrlPiece :: Dual a -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: Dual a -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: Dual a -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)
instance ToHttpApiData a => ToHttpApiData (Sum a) where
  toUrlPiece :: Sum a -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: Sum a -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: Sum a -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)
instance ToHttpApiData a => ToHttpApiData (Product a) where
  toUrlPiece :: Product a -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: Product a -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: Product a -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)
instance ToHttpApiData a => ToHttpApiData (First a) where
  toUrlPiece :: First a -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: Maybe a -> Text)
  toEncodedUrlPiece :: First a -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: Maybe a -> BS.Builder)
  toEncodedQueryParam :: First a -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: Maybe a -> BS.Builder)
instance ToHttpApiData a => ToHttpApiData (Last a) where
  toUrlPiece :: Last a -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: Maybe a -> Text)
  toEncodedUrlPiece :: Last a -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: Maybe a -> BS.Builder)
  toEncodedQueryParam :: Last a -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: Maybe a -> BS.Builder)
instance ToHttpApiData a => ToHttpApiData (Semi.Min a) where
  toUrlPiece :: Min a -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: Min a -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: Min a -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)
instance ToHttpApiData a => ToHttpApiData (Semi.Max a) where
  toUrlPiece :: Max a -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: Max a -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: Max a -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)
instance ToHttpApiData a => ToHttpApiData (Semi.First a) where
  toUrlPiece :: First a -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: First a -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: First a -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)
instance ToHttpApiData a => ToHttpApiData (Semi.Last a) where
  toUrlPiece :: Last a -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toEncodedUrlPiece :: Last a -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece :: a -> BS.Builder)
  toEncodedQueryParam :: Last a -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)
instance ToHttpApiData a => ToHttpApiData (Maybe a) where
  toUrlPiece :: Maybe a -> Text
toUrlPiece (Just a
x) = Text
"just " forall a. Semigroup a => a -> a -> a
<> forall a. ToHttpApiData a => a -> Text
toUrlPiece a
x
  toUrlPiece Maybe a
Nothing  = Text
"nothing"
instance (ToHttpApiData a, ToHttpApiData b) => ToHttpApiData (Either a b) where
  toUrlPiece :: Either a b -> Text
toUrlPiece (Left a
x)  = Text
"left " forall a. Semigroup a => a -> a -> a
<> forall a. ToHttpApiData a => a -> Text
toUrlPiece a
x
  toUrlPiece (Right b
x) = Text
"right " forall a. Semigroup a => a -> a -> a
<> forall a. ToHttpApiData a => a -> Text
toUrlPiece b
x
instance ToHttpApiData SetCookie where
  toUrlPiece :: SetCookie -> Text
toUrlPiece = OnDecodeError -> ByteString -> Text
decodeUtf8With OnDecodeError
lenientDecode forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToHttpApiData a => a -> ByteString
toHeader
  toHeader :: SetCookie -> ByteString
toHeader = ByteString -> ByteString
LBS.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
BS.toLazyByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. SetCookie -> Builder
renderSetCookie
  
instance ToHttpApiData a => ToHttpApiData (Tagged (b :: Type) a) where
  toUrlPiece :: Tagged b a -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toHeader :: Tagged b a -> ByteString
toHeader          = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> ByteString
toHeader :: a -> ByteString)
  toQueryParam :: Tagged b a -> Text
toQueryParam      = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toQueryParam :: a -> Text)
  toEncodedUrlPiece :: Tagged b a -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece ::  a -> BS.Builder)
  toEncodedQueryParam :: Tagged b a -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)
instance ToHttpApiData a => ToHttpApiData (Const a b) where
  toUrlPiece :: Const a b -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toHeader :: Const a b -> ByteString
toHeader          = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> ByteString
toHeader :: a -> ByteString)
  toQueryParam :: Const a b -> Text
toQueryParam      = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toQueryParam :: a -> Text)
  toEncodedUrlPiece :: Const a b -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece ::  a -> BS.Builder)
  toEncodedQueryParam :: Const a b -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)
instance ToHttpApiData a => ToHttpApiData (Identity a) where
  toUrlPiece :: Identity a -> Text
toUrlPiece        = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toUrlPiece :: a -> Text)
  toHeader :: Identity a -> ByteString
toHeader          = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> ByteString
toHeader :: a -> ByteString)
  toQueryParam :: Identity a -> Text
toQueryParam      = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Text
toQueryParam :: a -> Text)
  toEncodedUrlPiece :: Identity a -> Builder
toEncodedUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece ::  a -> BS.Builder)
  toEncodedQueryParam :: Identity a -> Builder
toEncodedQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. ToHttpApiData a => a -> Builder
toEncodedQueryParam :: a -> BS.Builder)
instance FromHttpApiData () where
  parseUrlPiece :: Text -> Either Text ()
parseUrlPiece Text
"_" = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
  parseUrlPiece Text
s   = 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' -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Char
c
      Maybe (Char, Text)
_            -> forall a. Text -> Either Text a
defaultParseError Text
s
instance FromHttpApiData Version where
  parseUrlPiece :: Text -> Either Text Version
parseUrlPiece Text
s =
    case forall a. [a] -> [a]
reverse (forall a. ReadP a -> ReadS a
readP_to_S ReadP Version
parseVersion (Text -> String
T.unpack Text
s)) of
      ((Version
x, String
""):[(Version, String)]
_) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Version
x
      [(Version, String)]
_           -> forall a. Text -> Either Text a
defaultParseError Text
s
instance FromHttpApiData Void where
  parseUrlPiece :: Text -> Either Text Void
parseUrlPiece Text
_ = 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 <- forall a. Reader a -> Text -> Either Text a
runReader (forall a. Num a => Reader a -> Reader a
signed forall a. Integral a => Reader a
decimal) Text
s
    if Integer
n forall a. Ord a => a -> a -> Bool
< Integer
0
      then forall a b. a -> Either a b
Left (Text
"underflow: " forall a. Semigroup a => a -> a -> a
<> Text
s forall a. Semigroup a => a -> a -> a
<> Text
" (should be a non-negative integer)")
      else forall a b. b -> Either a b
Right (forall a. Num a => Integer -> a
fromInteger Integer
n)
instance FromHttpApiData Bool     where parseUrlPiece :: Text -> Either Text Bool
parseUrlPiece = forall a.
(ToHttpApiData a, Bounded a, Enum a) =>
Text -> Either Text a
parseBoundedUrlPiece
instance FromHttpApiData Ordering where parseUrlPiece :: Text -> Either Text Ordering
parseUrlPiece = forall a.
(ToHttpApiData a, Bounded a, Enum a) =>
Text -> Either Text a
parseBoundedUrlPiece
instance FromHttpApiData Double   where parseUrlPiece :: Text -> Either Text Double
parseUrlPiece = forall a. Reader a -> Text -> Either Text a
runReader forall a. Fractional a => Reader a
rational
instance FromHttpApiData Float    where parseUrlPiece :: Text -> Either Text Float
parseUrlPiece = forall a. Reader a -> Text -> Either Text a
runReader forall a. Fractional a => Reader a
rational
instance FromHttpApiData Int      where parseUrlPiece :: Text -> Either Text Int
parseUrlPiece = forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded (forall a. Num a => Reader a -> Reader a
signed forall a. Integral a => Reader a
decimal)
instance FromHttpApiData Int8     where parseUrlPiece :: Text -> Either Text Int8
parseUrlPiece = forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded (forall a. Num a => Reader a -> Reader a
signed forall a. Integral a => Reader a
decimal)
instance FromHttpApiData Int16    where parseUrlPiece :: Text -> Either Text Int16
parseUrlPiece = forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded (forall a. Num a => Reader a -> Reader a
signed forall a. Integral a => Reader a
decimal)
instance FromHttpApiData Int32    where parseUrlPiece :: Text -> Either Text Int32
parseUrlPiece = forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded (forall a. Num a => Reader a -> Reader a
signed forall a. Integral a => Reader a
decimal)
instance FromHttpApiData Int64    where parseUrlPiece :: Text -> Either Text Int64
parseUrlPiece = forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded (forall a. Num a => Reader a -> Reader a
signed forall a. Integral a => Reader a
decimal)
instance FromHttpApiData Integer  where parseUrlPiece :: Text -> Either Text Integer
parseUrlPiece = forall a. Reader a -> Text -> Either Text a
runReader (forall a. Num a => Reader a -> Reader a
signed forall a. Integral a => Reader a
decimal)
instance FromHttpApiData Word     where parseUrlPiece :: Text -> Either Text Word
parseUrlPiece = forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded forall a. Integral a => Reader a
decimal
instance FromHttpApiData Word8    where parseUrlPiece :: Text -> Either Text Word8
parseUrlPiece = forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded forall a. Integral a => Reader a
decimal
instance FromHttpApiData Word16   where parseUrlPiece :: Text -> Either Text Word16
parseUrlPiece = forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded forall a. Integral a => Reader a
decimal
instance FromHttpApiData Word32   where parseUrlPiece :: Text -> Either Text Word32
parseUrlPiece = forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded forall a. Integral a => Reader a
decimal
instance FromHttpApiData Word64   where parseUrlPiece :: Text -> Either Text Word64
parseUrlPiece = forall a.
(Bounded a, Integral a) =>
Reader Integer -> Text -> Either Text a
parseBounded forall a. Integral a => Reader a
decimal
instance FromHttpApiData String   where parseUrlPiece :: Text -> Either Text String
parseUrlPiece = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
instance FromHttpApiData Text     where parseUrlPiece :: Text -> Either Text Text
parseUrlPiece = forall a b. b -> Either a b
Right
instance FromHttpApiData L.Text   where parseUrlPiece :: Text -> Either Text Text
parseUrlPiece = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
L.fromStrict
instance F.HasResolution a => FromHttpApiData (F.Fixed (a :: Type)) where
    parseUrlPiece :: Text -> Either Text (Fixed a)
parseUrlPiece = forall a. Reader a -> Text -> Either Text a
runReader forall a. Fractional a => Reader a
rational
instance FromHttpApiData Day where parseUrlPiece :: Text -> Either Text Day
parseUrlPiece = forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String Day
FT.parseDay
instance FromHttpApiData TimeOfDay where parseUrlPiece :: Text -> Either Text TimeOfDay
parseUrlPiece = forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String TimeOfDay
FT.parseTimeOfDay
instance FromHttpApiData LocalTime where parseUrlPiece :: Text -> Either Text LocalTime
parseUrlPiece = forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String LocalTime
FT.parseLocalTime
instance FromHttpApiData ZonedTime where parseUrlPiece :: Text -> Either Text ZonedTime
parseUrlPiece = forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String ZonedTime
FT.parseZonedTime
instance FromHttpApiData UTCTime   where parseUrlPiece :: Text -> Either Text UTCTime
parseUrlPiece = forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String UTCTime
FT.parseUTCTime
instance FromHttpApiData DayOfWeek where
  parseUrlPiece :: Text -> Either Text DayOfWeek
parseUrlPiece Text
t = case 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 -> forall a b. b -> Either a b
Right DayOfWeek
dow
      Maybe DayOfWeek
Nothing  -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Text
"Incorrect DayOfWeek: " 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 = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [ (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 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Pico -> NominalDiffTime
secondsToNominalDiffTime forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece
instance FromHttpApiData Month where parseUrlPiece :: Text -> Either Text Month
parseUrlPiece = forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String Month
FT.parseMonth
instance FromHttpApiData Quarter where parseUrlPiece :: Text -> Either Text Quarter
parseUrlPiece = forall a. (Text -> Either String a) -> Text -> Either Text a
runFT Text -> Either String Quarter
FT.parseQuarter
instance FromHttpApiData QuarterOfYear where parseUrlPiece :: Text -> Either Text QuarterOfYear
parseUrlPiece = 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 = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text Bool)
instance FromHttpApiData Any where parseUrlPiece :: Text -> Either Text Any
parseUrlPiece = coerce :: forall a b. Coercible a b => a -> b
coerce (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 = coerce :: forall a b. Coercible a b => a -> b
coerce (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 = coerce :: forall a b. Coercible a b => a -> b
coerce (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 = coerce :: forall a b. Coercible a b => a -> b
coerce (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 = coerce :: forall a b. Coercible a b => a -> b
coerce (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 = coerce :: forall a b. Coercible a b => a -> b
coerce (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 = coerce :: forall a b. Coercible a b => a -> b
coerce (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 = coerce :: forall a b. Coercible a b => a -> b
coerce (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 = coerce :: forall a b. Coercible a b => a -> b
coerce (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 = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
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) forall a. Eq a => a -> a -> Bool
== Text
"nothing" = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
    | Bool
otherwise                           = forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromHttpApiData a => Text -> Text -> Either Text a
parseUrlPieceWithPrefix Text
"Just " Text
s
instance (FromHttpApiData a, FromHttpApiData b) => FromHttpApiData (Either a b) where
  parseUrlPiece :: Text -> Either Text (Either a b)
parseUrlPiece Text
s =
        forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromHttpApiData a => Text -> Text -> Either Text a
parseUrlPieceWithPrefix Text
"Right " Text
s
    forall {a} {b}. Either a b -> Either a b -> Either a b
<!> forall a b. a -> Either a b
Left  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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 = forall a. ToHttpApiData a => a -> Builder
unsafeToEncodedUrlPiece
instance FromHttpApiData UUID.UUID where
    parseUrlPiece :: Text -> Either Text UUID
parseUrlPiece = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a b. a -> Either a b
Left Text
"invalid UUID") forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe UUID
UUID.fromText
    parseHeader :: ByteString -> Either Text UUID
parseHeader   = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a b. a -> Either a b
Left Text
"invalid UUID") forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe UUID
UUID.fromASCIIBytes
newtype LenientData a = LenientData { forall a. LenientData a -> Either Text a
getLenientData :: Either Text a }
    deriving (LenientData a -> LenientData a -> Bool
forall a. Eq a => LenientData a -> LenientData a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LenientData a -> LenientData a -> Bool
$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
Eq, 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
min :: LenientData a -> LenientData a -> LenientData a
$cmin :: forall a. Ord a => LenientData a -> LenientData a -> LenientData a
max :: LenientData a -> LenientData a -> LenientData a
$cmax :: forall a. Ord a => LenientData a -> LenientData a -> LenientData a
>= :: 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
$c< :: forall a. Ord a => LenientData a -> LenientData a -> Bool
compare :: LenientData a -> LenientData a -> Ordering
$ccompare :: forall a. Ord a => LenientData a -> LenientData a -> Ordering
Ord, Int -> LenientData a -> ShowS
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
showList :: [LenientData a] -> ShowS
$cshowList :: forall a. Show a => [LenientData a] -> ShowS
show :: LenientData a -> String
$cshow :: forall a. Show a => LenientData a -> String
showsPrec :: Int -> LenientData a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> LenientData a -> ShowS
Show, ReadPrec [LenientData a]
ReadPrec (LenientData a)
ReadS [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
readListPrec :: ReadPrec [LenientData a]
$creadListPrec :: forall a. Read a => ReadPrec [LenientData a]
readPrec :: ReadPrec (LenientData a)
$creadPrec :: forall a. Read a => ReadPrec (LenientData a)
readList :: ReadS [LenientData a]
$creadList :: forall a. Read a => ReadS [LenientData a]
readsPrec :: Int -> ReadS (LenientData a)
$creadsPrec :: forall a. Read a => Int -> ReadS (LenientData a)
Read, Typeable, LenientData a -> DataType
LenientData a -> Constr
forall {a}. Data a => Typeable (LenientData a)
forall a. Data a => LenientData a -> DataType
forall a. Data a => LenientData a -> Constr
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 (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))
gmapMo :: 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)
gmapMp :: forall (m :: * -> *).
MonadPlus 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)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> LenientData a -> m (LenientData a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> LenientData a -> m (LenientData a)
gmapQi :: forall u. Int -> (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
gmapQ :: forall u. (forall d. Data d => d -> u) -> LenientData a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> LenientData a -> [u]
gmapQr :: 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
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LenientData a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LenientData a -> r
gmapT :: (forall b. Data b => b -> b) -> LenientData a -> LenientData a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> LenientData a -> LenientData a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> 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))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (LenientData a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (LenientData a))
dataTypeOf :: LenientData a -> DataType
$cdataTypeOf :: forall a. Data a => LenientData a -> DataType
toConstr :: LenientData a -> Constr
$ctoConstr :: forall a. Data a => LenientData a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> 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)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LenientData a -> 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)
Data, 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
<$ :: forall a b. a -> LenientData b -> LenientData a
$c<$ :: forall a b. a -> LenientData b -> LenientData a
fmap :: forall a b. (a -> b) -> LenientData a -> LenientData b
$cfmap :: forall a b. (a -> b) -> LenientData a -> LenientData b
Functor, 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
product :: forall a. Num a => LenientData a -> a
$cproduct :: forall a. Num a => LenientData a -> a
sum :: forall a. Num a => LenientData a -> a
$csum :: forall a. Num a => LenientData a -> a
minimum :: forall a. Ord a => LenientData a -> a
$cminimum :: forall a. Ord a => LenientData a -> a
maximum :: forall a. Ord a => LenientData a -> a
$cmaximum :: forall a. Ord a => LenientData a -> a
elem :: forall a. Eq a => a -> LenientData a -> Bool
$celem :: forall a. Eq a => a -> LenientData a -> Bool
length :: forall a. LenientData a -> Int
$clength :: forall a. LenientData a -> Int
null :: forall a. LenientData a -> Bool
$cnull :: forall a. LenientData a -> Bool
toList :: forall a. LenientData a -> [a]
$ctoList :: forall a. LenientData a -> [a]
foldl1 :: forall a. (a -> a -> a) -> LenientData a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> LenientData a -> a
foldr1 :: forall a. (a -> a -> a) -> LenientData a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> LenientData a -> a
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
$cfoldl :: forall b a. (b -> a -> 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
$cfoldr :: forall a b. (a -> b -> b) -> b -> LenientData a -> b
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
$cfoldMap :: forall m a. Monoid m => (a -> m) -> LenientData a -> m
fold :: forall m. Monoid m => LenientData m -> m
$cfold :: forall m. Monoid m => LenientData m -> m
Foldable, Functor LenientData
Foldable 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)
sequence :: forall (m :: * -> *) a.
Monad m =>
LenientData (m a) -> m (LenientData a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
LenientData (m a) -> m (LenientData a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> LenientData a -> m (LenientData b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> LenientData a -> m (LenientData b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
LenientData (f a) -> f (LenientData a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
LenientData (f a) -> f (LenientData a)
traverse :: 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)
Traversable)
instance FromHttpApiData a => FromHttpApiData (LenientData a) where
    parseUrlPiece :: Text -> Either Text (LenientData a)
parseUrlPiece   = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Either Text a -> LenientData a
LenientData forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece
    parseHeader :: ByteString -> Either Text (LenientData a)
parseHeader     = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Either Text a -> LenientData a
LenientData forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader
    parseQueryParam :: Text -> Either Text (LenientData a)
parseQueryParam = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Either Text a -> LenientData a
LenientData forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam
instance FromHttpApiData SetCookie where
  parseUrlPiece :: Text -> Either Text SetCookie
parseUrlPiece = forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader  forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8
  parseHeader :: ByteString -> Either Text SetCookie
parseHeader   = forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> SetCookie
parseSetCookie
instance FromHttpApiData a => FromHttpApiData (Tagged (b :: Type) a) where
  parseUrlPiece :: Text -> Either Text (Tagged b a)
parseUrlPiece   = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
  parseHeader :: ByteString -> Either Text (Tagged b a)
parseHeader     = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader :: ByteString -> Either Text a)
  parseQueryParam :: Text -> Either Text (Tagged b a)
parseQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam :: Text -> Either Text a)
instance FromHttpApiData a => FromHttpApiData (Const a b) where
  parseUrlPiece :: Text -> Either Text (Const a b)
parseUrlPiece   = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
  parseHeader :: ByteString -> Either Text (Const a b)
parseHeader     = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader :: ByteString -> Either Text a)
  parseQueryParam :: Text -> Either Text (Const a b)
parseQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam :: Text -> Either Text a)
instance FromHttpApiData a => FromHttpApiData (Identity a) where
  parseUrlPiece :: Text -> Either Text (Identity a)
parseUrlPiece   = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. FromHttpApiData a => Text -> Either Text a
parseUrlPiece :: Text -> Either Text a)
  parseHeader :: ByteString -> Either Text (Identity a)
parseHeader     = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. FromHttpApiData a => ByteString -> Either Text a
parseHeader :: ByteString -> Either Text a)
  parseQueryParam :: Text -> Either Text (Identity a)
parseQueryParam = coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. FromHttpApiData a => Text -> Either Text a
parseQueryParam :: Text -> Either Text a)
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 -> forall a b. a -> Either a b
Left (String -> Text
T.pack String
err)
    Right a
x  -> forall a b. b -> Either a b
Right a
x