{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds -fno-warn-unused-imports #-}
module GenAI.Client.Core where
import GenAI.Client.Logging
import GenAI.Client.MimeTypes
import Control.Arrow qualified as P (left)
import Control.DeepSeq qualified as NF
import Control.Exception.Safe qualified as E
import Data.Aeson qualified as A
import Data.ByteString qualified as B
import Data.ByteString.Base64.Lazy qualified as BL64
import Data.ByteString.Builder qualified as BB
import Data.ByteString.Char8 qualified as BC
import Data.ByteString.Lazy qualified as BL
import Data.ByteString.Lazy.Char8 qualified as BCL
import Data.CaseInsensitive qualified as CI
import Data.Data qualified as P (Data, TypeRep, Typeable, typeRep)
import Data.Foldable qualified as P
import Data.Ix qualified as P
import Data.Kind qualified as K (Type)
import Data.Maybe qualified as P
import Data.Proxy qualified as P (Proxy (..))
import Data.Text qualified as T
import Data.Text.Encoding qualified as T
import Data.Text.Lazy.Encoding qualified as TL
import Data.Time qualified as TI
import Data.Time.ISO8601 qualified as TI
import GHC.Base qualified as P (Alternative)
import Lens.Micro qualified as L
import Network.HTTP.Client.MultipartFormData qualified as NH
import Network.HTTP.Types qualified as NH
import Text.Printf qualified as T
import Web.FormUrlEncoded qualified as WH
import Web.HttpApiData qualified as WH
import Prelude qualified as P
import Control.Applicative (Alternative, (<|>))
import Control.Monad.Fail (MonadFail)
import Data.Foldable (foldlM)
import Data.Function ((&))
import Data.Monoid ((<>))
import Data.Text (Text)
import Prelude (Bool (..), Char, Functor, IO, Maybe (..), Monad, String, fmap, maybe, mempty, pure, return, show, ($), (&&), (.), (<$>), (<*>))
data GenAIClientConfig = GenAIClientConfig
{ GenAIClientConfig -> ByteString
configHost :: BCL.ByteString
, GenAIClientConfig -> Text
configUserAgent :: Text
, GenAIClientConfig -> LogExecWithContext
configLogExecWithContext :: LogExecWithContext
, GenAIClientConfig -> LogContext
configLogContext :: LogContext
, GenAIClientConfig -> [AnyAuthMethod]
configAuthMethods :: [AnyAuthMethod]
, GenAIClientConfig -> Bool
configValidateAuthMethods :: Bool
, :: B.ByteString
}
instance P.Show GenAIClientConfig where
show :: GenAIClientConfig -> String
show GenAIClientConfig
c =
String -> String -> ShowS
forall r. PrintfType r => String -> r
T.printf
String
"{ configHost = %v, configUserAgent = %v, ..}"
(ByteString -> String
forall a. Show a => a -> String
show (GenAIClientConfig -> ByteString
configHost GenAIClientConfig
c))
(Text -> String
forall a. Show a => a -> String
show (GenAIClientConfig -> Text
configUserAgent GenAIClientConfig
c))
newConfig :: IO GenAIClientConfig
newConfig :: IO GenAIClientConfig
newConfig = do
LogContext
logCxt <- IO LogContext
initLogContext
GenAIClientConfig -> IO GenAIClientConfig
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenAIClientConfig -> IO GenAIClientConfig)
-> GenAIClientConfig -> IO GenAIClientConfig
forall a b. (a -> b) -> a -> b
$
GenAIClientConfig
{ configHost :: ByteString
configHost = ByteString
"https://generativelanguage.googleapis.com"
, configUserAgent :: Text
configUserAgent = Text
"haskell-google-genai-client/0.1.0.0"
, configLogExecWithContext :: LogExecWithContext
configLogExecWithContext = LogContext -> LogExec m a
LogExecWithContext
runDefaultLogExecWithContext
, configLogContext :: LogContext
configLogContext = LogContext
logCxt
, configAuthMethods :: [AnyAuthMethod]
configAuthMethods = []
, configValidateAuthMethods :: Bool
configValidateAuthMethods = Bool
True
, configQueryExtraUnreserved :: ByteString
configQueryExtraUnreserved = ByteString
""
}
addAuthMethod :: (AuthMethod auth) => GenAIClientConfig -> auth -> GenAIClientConfig
addAuthMethod :: forall auth.
AuthMethod auth =>
GenAIClientConfig -> auth -> GenAIClientConfig
addAuthMethod config :: GenAIClientConfig
config@GenAIClientConfig {configAuthMethods :: GenAIClientConfig -> [AnyAuthMethod]
configAuthMethods = [AnyAuthMethod]
as} auth
a =
GenAIClientConfig
config {configAuthMethods = AnyAuthMethod a : as}
withStdoutLogging :: GenAIClientConfig -> IO GenAIClientConfig
withStdoutLogging :: GenAIClientConfig -> IO GenAIClientConfig
withStdoutLogging GenAIClientConfig
p = do
LogContext
logCxt <- LogContext -> IO LogContext
stdoutLoggingContext (GenAIClientConfig -> LogContext
configLogContext GenAIClientConfig
p)
GenAIClientConfig -> IO GenAIClientConfig
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenAIClientConfig -> IO GenAIClientConfig)
-> GenAIClientConfig -> IO GenAIClientConfig
forall a b. (a -> b) -> a -> b
$ GenAIClientConfig
p {configLogExecWithContext = stdoutLoggingExec, configLogContext = logCxt}
withStderrLogging :: GenAIClientConfig -> IO GenAIClientConfig
withStderrLogging :: GenAIClientConfig -> IO GenAIClientConfig
withStderrLogging GenAIClientConfig
p = do
LogContext
logCxt <- LogContext -> IO LogContext
stderrLoggingContext (GenAIClientConfig -> LogContext
configLogContext GenAIClientConfig
p)
GenAIClientConfig -> IO GenAIClientConfig
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (GenAIClientConfig -> IO GenAIClientConfig)
-> GenAIClientConfig -> IO GenAIClientConfig
forall a b. (a -> b) -> a -> b
$ GenAIClientConfig
p {configLogExecWithContext = stderrLoggingExec, configLogContext = logCxt}
withNoLogging :: GenAIClientConfig -> GenAIClientConfig
withNoLogging :: GenAIClientConfig -> GenAIClientConfig
withNoLogging GenAIClientConfig
p = GenAIClientConfig
p {configLogExecWithContext = runNullLogExec}
data ClientRequest req contentType res accept = ClientRequest
{ forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> ByteString
rMethod :: NH.Method
, forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> [ByteString]
rUrlPath :: [BCL.ByteString]
, forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> Params
rParams :: Params
, forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> [TypeRep]
rAuthTypes :: [P.TypeRep]
}
deriving (Int -> ClientRequest req contentType res accept -> ShowS
[ClientRequest req contentType res accept] -> ShowS
ClientRequest req contentType res accept -> String
(Int -> ClientRequest req contentType res accept -> ShowS)
-> (ClientRequest req contentType res accept -> String)
-> ([ClientRequest req contentType res accept] -> ShowS)
-> Show (ClientRequest req contentType res accept)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (req :: k) k (contentType :: k) k (res :: k) k
(accept :: k).
Int -> ClientRequest req contentType res accept -> ShowS
forall k (req :: k) k (contentType :: k) k (res :: k) k
(accept :: k).
[ClientRequest req contentType res accept] -> ShowS
forall k (req :: k) k (contentType :: k) k (res :: k) k
(accept :: k).
ClientRequest req contentType res accept -> String
$cshowsPrec :: forall k (req :: k) k (contentType :: k) k (res :: k) k
(accept :: k).
Int -> ClientRequest req contentType res accept -> ShowS
showsPrec :: Int -> ClientRequest req contentType res accept -> ShowS
$cshow :: forall k (req :: k) k (contentType :: k) k (res :: k) k
(accept :: k).
ClientRequest req contentType res accept -> String
show :: ClientRequest req contentType res accept -> String
$cshowList :: forall k (req :: k) k (contentType :: k) k (res :: k) k
(accept :: k).
[ClientRequest req contentType res accept] -> ShowS
showList :: [ClientRequest req contentType res accept] -> ShowS
P.Show)
rMethodL :: Lens_' (ClientRequest req contentType res accept) NH.Method
rMethodL :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
(ByteString -> f ByteString)
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rMethodL ByteString -> f ByteString
f ClientRequest {[TypeRep]
[ByteString]
ByteString
Params
rMethod :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> ByteString
rUrlPath :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> [ByteString]
rParams :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> Params
rAuthTypes :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> [TypeRep]
rMethod :: ByteString
rUrlPath :: [ByteString]
rParams :: Params
rAuthTypes :: [TypeRep]
..} = (\ByteString
rMethod -> ClientRequest {ByteString
rMethod :: ByteString
rMethod :: ByteString
rMethod, [TypeRep]
[ByteString]
Params
rUrlPath :: [ByteString]
rParams :: Params
rAuthTypes :: [TypeRep]
rUrlPath :: [ByteString]
rParams :: Params
rAuthTypes :: [TypeRep]
..}) (ByteString -> ClientRequest req contentType res accept)
-> f ByteString -> f (ClientRequest req contentType res accept)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> f ByteString
f ByteString
rMethod
{-# INLINE rMethodL #-}
rUrlPathL :: Lens_' (ClientRequest req contentType res accept) [BCL.ByteString]
rUrlPathL :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
([ByteString] -> f [ByteString])
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rUrlPathL [ByteString] -> f [ByteString]
f ClientRequest {[TypeRep]
[ByteString]
ByteString
Params
rMethod :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> ByteString
rUrlPath :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> [ByteString]
rParams :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> Params
rAuthTypes :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> [TypeRep]
rMethod :: ByteString
rUrlPath :: [ByteString]
rParams :: Params
rAuthTypes :: [TypeRep]
..} = (\[ByteString]
rUrlPath -> ClientRequest {[ByteString]
rUrlPath :: [ByteString]
rUrlPath :: [ByteString]
rUrlPath, [TypeRep]
ByteString
Params
rMethod :: ByteString
rParams :: Params
rAuthTypes :: [TypeRep]
rMethod :: ByteString
rParams :: Params
rAuthTypes :: [TypeRep]
..}) ([ByteString] -> ClientRequest req contentType res accept)
-> f [ByteString] -> f (ClientRequest req contentType res accept)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ByteString] -> f [ByteString]
f [ByteString]
rUrlPath
{-# INLINE rUrlPathL #-}
rParamsL :: Lens_' (ClientRequest req contentType res accept) Params
rParamsL :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
(Params -> f Params)
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rParamsL Params -> f Params
f ClientRequest {[TypeRep]
[ByteString]
ByteString
Params
rMethod :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> ByteString
rUrlPath :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> [ByteString]
rParams :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> Params
rAuthTypes :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> [TypeRep]
rMethod :: ByteString
rUrlPath :: [ByteString]
rParams :: Params
rAuthTypes :: [TypeRep]
..} = (\Params
rParams -> ClientRequest {Params
rParams :: Params
rParams :: Params
rParams, [TypeRep]
[ByteString]
ByteString
rMethod :: ByteString
rUrlPath :: [ByteString]
rAuthTypes :: [TypeRep]
rMethod :: ByteString
rUrlPath :: [ByteString]
rAuthTypes :: [TypeRep]
..}) (Params -> ClientRequest req contentType res accept)
-> f Params -> f (ClientRequest req contentType res accept)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Params -> f Params
f Params
rParams
{-# INLINE rParamsL #-}
rAuthTypesL :: Lens_' (ClientRequest req contentType res accept) [P.TypeRep]
rAuthTypesL :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
([TypeRep] -> f [TypeRep])
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rAuthTypesL [TypeRep] -> f [TypeRep]
f ClientRequest {[TypeRep]
[ByteString]
ByteString
Params
rMethod :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> ByteString
rUrlPath :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> [ByteString]
rParams :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> Params
rAuthTypes :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> [TypeRep]
rMethod :: ByteString
rUrlPath :: [ByteString]
rParams :: Params
rAuthTypes :: [TypeRep]
..} = (\[TypeRep]
rAuthTypes -> ClientRequest {[TypeRep]
rAuthTypes :: [TypeRep]
rAuthTypes :: [TypeRep]
rAuthTypes, [ByteString]
ByteString
Params
rMethod :: ByteString
rUrlPath :: [ByteString]
rParams :: Params
rMethod :: ByteString
rUrlPath :: [ByteString]
rParams :: Params
..}) ([TypeRep] -> ClientRequest req contentType res accept)
-> f [TypeRep] -> f (ClientRequest req contentType res accept)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [TypeRep] -> f [TypeRep]
f [TypeRep]
rAuthTypes
{-# INLINE rAuthTypesL #-}
class HasBodyParam req param where
setBodyParam :: forall contentType res accept. (Consumes req contentType, MimeRender contentType param) => ClientRequest req contentType res accept -> param -> ClientRequest req contentType res accept
setBodyParam ClientRequest req contentType res accept
req param
xs =
ClientRequest req contentType res accept
req ClientRequest req contentType res accept
-> ByteString -> ClientRequest req contentType res accept
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> ByteString -> ClientRequest req contentType res accept
`_setBodyLBS` Proxy contentType -> param -> ByteString
forall mtype x.
MimeRender mtype x =>
Proxy mtype -> x -> ByteString
mimeRender (Proxy contentType
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy contentType) param
xs ClientRequest req contentType res accept
-> (ClientRequest req contentType res accept
-> ClientRequest req contentType res accept)
-> ClientRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ClientRequest req contentType res accept
-> ClientRequest req contentType res accept
forall {k} {k} {k} (req :: k) contentType (res :: k) (accept :: k).
MimeType contentType =>
ClientRequest req contentType res accept
-> ClientRequest req contentType res accept
_setContentTypeHeader
class HasOptionalParam req param where
{-# MINIMAL applyOptionalParam | (-&-) #-}
applyOptionalParam :: ClientRequest req contentType res accept -> param -> ClientRequest req contentType res accept
applyOptionalParam = ClientRequest req contentType res accept
-> param -> ClientRequest req contentType res accept
forall {k} (req :: k) param {k} {k} {k} (contentType :: k)
(res :: k) (accept :: k).
HasOptionalParam req param =>
ClientRequest req contentType res accept
-> param -> ClientRequest req contentType res accept
forall {k} {k} {k} (contentType :: k) (res :: k) (accept :: k).
ClientRequest req contentType res accept
-> param -> ClientRequest req contentType res accept
(-&-)
{-# INLINE applyOptionalParam #-}
(-&-) :: ClientRequest req contentType res accept -> param -> ClientRequest req contentType res accept
(-&-) = ClientRequest req contentType res accept
-> param -> ClientRequest req contentType res accept
forall {k} (req :: k) param {k} {k} {k} (contentType :: k)
(res :: k) (accept :: k).
HasOptionalParam req param =>
ClientRequest req contentType res accept
-> param -> ClientRequest req contentType res accept
forall {k} {k} {k} (contentType :: k) (res :: k) (accept :: k).
ClientRequest req contentType res accept
-> param -> ClientRequest req contentType res accept
applyOptionalParam
{-# INLINE (-&-) #-}
infixl 2 -&-
data Params = Params
{ Params -> Query
paramsQuery :: NH.Query
, :: NH.RequestHeaders
, Params -> ParamBody
paramsBody :: ParamBody
}
deriving (Int -> Params -> ShowS
[Params] -> ShowS
Params -> String
(Int -> Params -> ShowS)
-> (Params -> String) -> ([Params] -> ShowS) -> Show Params
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Params -> ShowS
showsPrec :: Int -> Params -> ShowS
$cshow :: Params -> String
show :: Params -> String
$cshowList :: [Params] -> ShowS
showList :: [Params] -> ShowS
P.Show)
paramsQueryL :: Lens_' Params NH.Query
paramsQueryL :: Lens_' Params Query
paramsQueryL Query -> f Query
f Params {Query
RequestHeaders
ParamBody
paramsQuery :: Params -> Query
paramsHeaders :: Params -> RequestHeaders
paramsBody :: Params -> ParamBody
paramsQuery :: Query
paramsHeaders :: RequestHeaders
paramsBody :: ParamBody
..} = (\Query
paramsQuery -> Params {Query
paramsQuery :: Query
paramsQuery :: Query
paramsQuery, RequestHeaders
ParamBody
paramsHeaders :: RequestHeaders
paramsBody :: ParamBody
paramsHeaders :: RequestHeaders
paramsBody :: ParamBody
..}) (Query -> Params) -> f Query -> f Params
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> f Query
f Query
paramsQuery
{-# INLINE paramsQueryL #-}
paramsHeadersL :: Lens_' Params NH.RequestHeaders
RequestHeaders -> f RequestHeaders
f Params {Query
RequestHeaders
ParamBody
paramsQuery :: Params -> Query
paramsHeaders :: Params -> RequestHeaders
paramsBody :: Params -> ParamBody
paramsQuery :: Query
paramsHeaders :: RequestHeaders
paramsBody :: ParamBody
..} = (\RequestHeaders
paramsHeaders -> Params {RequestHeaders
paramsHeaders :: RequestHeaders
paramsHeaders :: RequestHeaders
paramsHeaders, Query
ParamBody
paramsQuery :: Query
paramsBody :: ParamBody
paramsQuery :: Query
paramsBody :: ParamBody
..}) (RequestHeaders -> Params) -> f RequestHeaders -> f Params
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RequestHeaders -> f RequestHeaders
f RequestHeaders
paramsHeaders
{-# INLINE paramsHeadersL #-}
paramsBodyL :: Lens_' Params ParamBody
paramsBodyL :: Lens_' Params ParamBody
paramsBodyL ParamBody -> f ParamBody
f Params {Query
RequestHeaders
ParamBody
paramsQuery :: Params -> Query
paramsHeaders :: Params -> RequestHeaders
paramsBody :: Params -> ParamBody
paramsQuery :: Query
paramsHeaders :: RequestHeaders
paramsBody :: ParamBody
..} = (\ParamBody
paramsBody -> Params {ParamBody
paramsBody :: ParamBody
paramsBody :: ParamBody
paramsBody, Query
RequestHeaders
paramsQuery :: Query
paramsHeaders :: RequestHeaders
paramsQuery :: Query
paramsHeaders :: RequestHeaders
..}) (ParamBody -> Params) -> f ParamBody -> f Params
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParamBody -> f ParamBody
f ParamBody
paramsBody
{-# INLINE paramsBodyL #-}
data ParamBody
= ParamBodyNone
| ParamBodyB B.ByteString
| ParamBodyBL BL.ByteString
| ParamBodyFormUrlEncoded WH.Form
| ParamBodyMultipartFormData [NH.Part]
deriving (Int -> ParamBody -> ShowS
[ParamBody] -> ShowS
ParamBody -> String
(Int -> ParamBody -> ShowS)
-> (ParamBody -> String)
-> ([ParamBody] -> ShowS)
-> Show ParamBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParamBody -> ShowS
showsPrec :: Int -> ParamBody -> ShowS
$cshow :: ParamBody -> String
show :: ParamBody -> String
$cshowList :: [ParamBody] -> ShowS
showList :: [ParamBody] -> ShowS
P.Show)
_mkRequest ::
NH.Method ->
[BCL.ByteString] ->
ClientRequest req contentType res accept
_mkRequest :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ByteString
-> [ByteString] -> ClientRequest req contentType res accept
_mkRequest ByteString
m [ByteString]
u = ByteString
-> [ByteString]
-> Params
-> [TypeRep]
-> ClientRequest req contentType res accept
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ByteString
-> [ByteString]
-> Params
-> [TypeRep]
-> ClientRequest req contentType res accept
ClientRequest ByteString
m [ByteString]
u Params
_mkParams []
_mkParams :: Params
_mkParams :: Params
_mkParams = Query -> RequestHeaders -> ParamBody -> Params
Params [] [] ParamBody
ParamBodyNone
setHeader ::
ClientRequest req contentType res accept ->
[NH.Header] ->
ClientRequest req contentType res accept
ClientRequest req contentType res accept
req RequestHeaders
header =
ClientRequest req contentType res accept
req ClientRequest req contentType res accept
-> [HeaderName] -> ClientRequest req contentType res accept
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> [HeaderName] -> ClientRequest req contentType res accept
`removeHeader` ((HeaderName, ByteString) -> HeaderName)
-> RequestHeaders -> [HeaderName]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap (HeaderName, ByteString) -> HeaderName
forall a b. (a, b) -> a
P.fst RequestHeaders
header
ClientRequest req contentType res accept
-> (ClientRequest req contentType res accept
-> ClientRequest req contentType res accept)
-> ClientRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& (ClientRequest req contentType res accept
-> RequestHeaders -> ClientRequest req contentType res accept
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> RequestHeaders -> ClientRequest req contentType res accept
`addHeader` RequestHeaders
header)
addHeader ::
ClientRequest req contentType res accept ->
[NH.Header] ->
ClientRequest req contentType res accept
ClientRequest req contentType res accept
req RequestHeaders
header = ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
RequestHeaders
RequestHeaders
-> (RequestHeaders -> RequestHeaders)
-> ClientRequest req contentType res accept
-> ClientRequest req contentType res accept
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept)
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
(Params -> f Params)
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rParamsL ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept))
-> ((RequestHeaders -> Identity RequestHeaders)
-> Params -> Identity Params)
-> ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
RequestHeaders
RequestHeaders
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RequestHeaders -> Identity RequestHeaders)
-> Params -> Identity Params
Lens_' Params RequestHeaders
paramsHeadersL) (RequestHeaders
header P.++) ClientRequest req contentType res accept
req
removeHeader :: ClientRequest req contentType res accept -> [NH.HeaderName] -> ClientRequest req contentType res accept
ClientRequest req contentType res accept
req [HeaderName]
header =
ClientRequest req contentType res accept
req
ClientRequest req contentType res accept
-> (ClientRequest req contentType res accept
-> ClientRequest req contentType res accept)
-> ClientRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
RequestHeaders
RequestHeaders
-> (RequestHeaders -> RequestHeaders)
-> ClientRequest req contentType res accept
-> ClientRequest req contentType res accept
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over
((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept)
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
(Params -> f Params)
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rParamsL ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept))
-> ((RequestHeaders -> Identity RequestHeaders)
-> Params -> Identity Params)
-> ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
RequestHeaders
RequestHeaders
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RequestHeaders -> Identity RequestHeaders)
-> Params -> Identity Params
Lens_' Params RequestHeaders
paramsHeadersL)
(((HeaderName, ByteString) -> Bool)
-> RequestHeaders -> RequestHeaders
forall a. (a -> Bool) -> [a] -> [a]
P.filter (\(HeaderName, ByteString)
h -> (HeaderName, ByteString) -> CI HeaderName
forall {b}. (HeaderName, b) -> CI HeaderName
cifst (HeaderName, ByteString)
h CI HeaderName -> [CI HeaderName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`P.notElem` (HeaderName -> CI HeaderName) -> [HeaderName] -> [CI HeaderName]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap HeaderName -> CI HeaderName
forall s. FoldCase s => s -> CI s
CI.mk [HeaderName]
header))
where
cifst :: (HeaderName, b) -> CI HeaderName
cifst = HeaderName -> CI HeaderName
forall s. FoldCase s => s -> CI s
CI.mk (HeaderName -> CI HeaderName)
-> ((HeaderName, b) -> HeaderName)
-> (HeaderName, b)
-> CI HeaderName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HeaderName, b) -> HeaderName
forall a b. (a, b) -> a
P.fst
_setContentTypeHeader :: forall req contentType res accept. (MimeType contentType) => ClientRequest req contentType res accept -> ClientRequest req contentType res accept
ClientRequest req contentType res accept
req =
case Proxy contentType -> Maybe MediaType
forall mtype. MimeType mtype => Proxy mtype -> Maybe MediaType
mimeType (Proxy contentType
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy contentType) of
Just MediaType
m -> ClientRequest req contentType res accept
req ClientRequest req contentType res accept
-> RequestHeaders -> ClientRequest req contentType res accept
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> RequestHeaders -> ClientRequest req contentType res accept
`setHeader` [(HeaderName
"content-type", String -> ByteString
BC.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ MediaType -> String
forall a. Show a => a -> String
P.show MediaType
m)]
Maybe MediaType
Nothing -> ClientRequest req contentType res accept
req ClientRequest req contentType res accept
-> [HeaderName] -> ClientRequest req contentType res accept
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> [HeaderName] -> ClientRequest req contentType res accept
`removeHeader` [HeaderName
"content-type"]
_setAcceptHeader :: forall req contentType res accept. (MimeType accept) => ClientRequest req contentType res accept -> ClientRequest req contentType res accept
ClientRequest req contentType res accept
req =
case Proxy accept -> Maybe MediaType
forall mtype. MimeType mtype => Proxy mtype -> Maybe MediaType
mimeType (Proxy accept
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy accept) of
Just MediaType
m -> ClientRequest req contentType res accept
req ClientRequest req contentType res accept
-> RequestHeaders -> ClientRequest req contentType res accept
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> RequestHeaders -> ClientRequest req contentType res accept
`setHeader` [(HeaderName
"accept", String -> ByteString
BC.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ MediaType -> String
forall a. Show a => a -> String
P.show MediaType
m)]
Maybe MediaType
Nothing -> ClientRequest req contentType res accept
req ClientRequest req contentType res accept
-> [HeaderName] -> ClientRequest req contentType res accept
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> [HeaderName] -> ClientRequest req contentType res accept
`removeHeader` [HeaderName
"accept"]
setQuery ::
ClientRequest req contentType res accept ->
[NH.QueryItem] ->
ClientRequest req contentType res accept
setQuery :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> Query -> ClientRequest req contentType res accept
setQuery ClientRequest req contentType res accept
req Query
query =
ClientRequest req contentType res accept
req
ClientRequest req contentType res accept
-> (ClientRequest req contentType res accept
-> ClientRequest req contentType res accept)
-> ClientRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
Query
Query
-> (Query -> Query)
-> ClientRequest req contentType res accept
-> ClientRequest req contentType res accept
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over
((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept)
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
(Params -> f Params)
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rParamsL ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept))
-> ((Query -> Identity Query) -> Params -> Identity Params)
-> ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
Query
Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Query -> Identity Query) -> Params -> Identity Params
Lens_' Params Query
paramsQueryL)
(((ByteString, Maybe ByteString) -> Bool) -> Query -> Query
forall a. (a -> Bool) -> [a] -> [a]
P.filter (\(ByteString, Maybe ByteString)
q -> (ByteString, Maybe ByteString) -> HeaderName
forall {b}. (ByteString, b) -> HeaderName
cifst (ByteString, Maybe ByteString)
q HeaderName -> [HeaderName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`P.notElem` ((ByteString, Maybe ByteString) -> HeaderName)
-> Query -> [HeaderName]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap (ByteString, Maybe ByteString) -> HeaderName
forall {b}. (ByteString, b) -> HeaderName
cifst Query
query))
ClientRequest req contentType res accept
-> (ClientRequest req contentType res accept
-> ClientRequest req contentType res accept)
-> ClientRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& (ClientRequest req contentType res accept
-> Query -> ClientRequest req contentType res accept
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> Query -> ClientRequest req contentType res accept
`addQuery` Query
query)
where
cifst :: (ByteString, b) -> HeaderName
cifst = ByteString -> HeaderName
forall s. FoldCase s => s -> CI s
CI.mk (ByteString -> HeaderName)
-> ((ByteString, b) -> ByteString) -> (ByteString, b) -> HeaderName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString, b) -> ByteString
forall a b. (a, b) -> a
P.fst
addQuery ::
ClientRequest req contentType res accept ->
[NH.QueryItem] ->
ClientRequest req contentType res accept
addQuery :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> Query -> ClientRequest req contentType res accept
addQuery ClientRequest req contentType res accept
req Query
query = ClientRequest req contentType res accept
req ClientRequest req contentType res accept
-> (ClientRequest req contentType res accept
-> ClientRequest req contentType res accept)
-> ClientRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
Query
Query
-> (Query -> Query)
-> ClientRequest req contentType res accept
-> ClientRequest req contentType res accept
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept)
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
(Params -> f Params)
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rParamsL ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept))
-> ((Query -> Identity Query) -> Params -> Identity Params)
-> ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
Query
Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Query -> Identity Query) -> Params -> Identity Params
Lens_' Params Query
paramsQueryL) (Query
query P.++)
addForm :: ClientRequest req contentType res accept -> WH.Form -> ClientRequest req contentType res accept
addForm :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> Form -> ClientRequest req contentType res accept
addForm ClientRequest req contentType res accept
req Form
newform =
let form :: Form
form = case Params -> ParamBody
paramsBody (ClientRequest req contentType res accept -> Params
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> Params
rParams ClientRequest req contentType res accept
req) of
ParamBodyFormUrlEncoded Form
_form -> Form
_form
ParamBody
_ -> Form
forall a. Monoid a => a
mempty
in ClientRequest req contentType res accept
req ClientRequest req contentType res accept
-> (ClientRequest req contentType res accept
-> ClientRequest req contentType res accept)
-> ClientRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
ParamBody
ParamBody
-> ParamBody
-> ClientRequest req contentType res accept
-> ClientRequest req contentType res accept
forall s t a b. ASetter s t a b -> b -> s -> t
L.set ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept)
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
(Params -> f Params)
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rParamsL ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept))
-> ((ParamBody -> Identity ParamBody) -> Params -> Identity Params)
-> ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
ParamBody
ParamBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParamBody -> Identity ParamBody) -> Params -> Identity Params
Lens_' Params ParamBody
paramsBodyL) (Form -> ParamBody
ParamBodyFormUrlEncoded (Form
newform Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> Form
form))
_addMultiFormPart :: ClientRequest req contentType res accept -> NH.Part -> ClientRequest req contentType res accept
_addMultiFormPart :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> Part -> ClientRequest req contentType res accept
_addMultiFormPart ClientRequest req contentType res accept
req Part
newpart =
let parts :: [Part]
parts = case Params -> ParamBody
paramsBody (ClientRequest req contentType res accept -> Params
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept -> Params
rParams ClientRequest req contentType res accept
req) of
ParamBodyMultipartFormData [Part]
_parts -> [Part]
_parts
ParamBody
_ -> []
in ClientRequest req contentType res accept
req ClientRequest req contentType res accept
-> (ClientRequest req contentType res accept
-> ClientRequest req contentType res accept)
-> ClientRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
ParamBody
ParamBody
-> ParamBody
-> ClientRequest req contentType res accept
-> ClientRequest req contentType res accept
forall s t a b. ASetter s t a b -> b -> s -> t
L.set ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept)
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
(Params -> f Params)
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rParamsL ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept))
-> ((ParamBody -> Identity ParamBody) -> Params -> Identity Params)
-> ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
ParamBody
ParamBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParamBody -> Identity ParamBody) -> Params -> Identity Params
Lens_' Params ParamBody
paramsBodyL) ([Part] -> ParamBody
ParamBodyMultipartFormData (Part
newpart Part -> [Part] -> [Part]
forall a. a -> [a] -> [a]
: [Part]
parts))
_setBodyBS :: ClientRequest req contentType res accept -> B.ByteString -> ClientRequest req contentType res accept
_setBodyBS :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> ByteString -> ClientRequest req contentType res accept
_setBodyBS ClientRequest req contentType res accept
req ByteString
body =
ClientRequest req contentType res accept
req ClientRequest req contentType res accept
-> (ClientRequest req contentType res accept
-> ClientRequest req contentType res accept)
-> ClientRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
ParamBody
ParamBody
-> ParamBody
-> ClientRequest req contentType res accept
-> ClientRequest req contentType res accept
forall s t a b. ASetter s t a b -> b -> s -> t
L.set ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept)
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
(Params -> f Params)
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rParamsL ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept))
-> ((ParamBody -> Identity ParamBody) -> Params -> Identity Params)
-> ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
ParamBody
ParamBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParamBody -> Identity ParamBody) -> Params -> Identity Params
Lens_' Params ParamBody
paramsBodyL) (ByteString -> ParamBody
ParamBodyB ByteString
body)
_setBodyLBS :: ClientRequest req contentType res accept -> BL.ByteString -> ClientRequest req contentType res accept
_setBodyLBS :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> ByteString -> ClientRequest req contentType res accept
_setBodyLBS ClientRequest req contentType res accept
req ByteString
body =
ClientRequest req contentType res accept
req ClientRequest req contentType res accept
-> (ClientRequest req contentType res accept
-> ClientRequest req contentType res accept)
-> ClientRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
ParamBody
ParamBody
-> ParamBody
-> ClientRequest req contentType res accept
-> ClientRequest req contentType res accept
forall s t a b. ASetter s t a b -> b -> s -> t
L.set ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept)
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
(Params -> f Params)
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rParamsL ((Params -> Identity Params)
-> ClientRequest req contentType res accept
-> Identity (ClientRequest req contentType res accept))
-> ((ParamBody -> Identity ParamBody) -> Params -> Identity Params)
-> ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
ParamBody
ParamBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParamBody -> Identity ParamBody) -> Params -> Identity Params
Lens_' Params ParamBody
paramsBodyL) (ByteString -> ParamBody
ParamBodyBL ByteString
body)
_hasAuthType :: (AuthMethod authMethod) => ClientRequest req contentType res accept -> P.Proxy authMethod -> ClientRequest req contentType res accept
_hasAuthType :: forall {k} {k} {k} {k} authMethod (req :: k) (contentType :: k)
(res :: k) (accept :: k).
AuthMethod authMethod =>
ClientRequest req contentType res accept
-> Proxy authMethod -> ClientRequest req contentType res accept
_hasAuthType ClientRequest req contentType res accept
req Proxy authMethod
proxy =
ClientRequest req contentType res accept
req ClientRequest req contentType res accept
-> (ClientRequest req contentType res accept
-> ClientRequest req contentType res accept)
-> ClientRequest req contentType res accept
forall a b. a -> (a -> b) -> b
& ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
[TypeRep]
[TypeRep]
-> ([TypeRep] -> [TypeRep])
-> ClientRequest req contentType res accept
-> ClientRequest req contentType res accept
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
L.over ASetter
(ClientRequest req contentType res accept)
(ClientRequest req contentType res accept)
[TypeRep]
[TypeRep]
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k) (f :: * -> *).
Functor f =>
([TypeRep] -> f [TypeRep])
-> ClientRequest req contentType res accept
-> f (ClientRequest req contentType res accept)
rAuthTypesL (Proxy authMethod -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
P.typeRep Proxy authMethod
proxy :)
toPath ::
(WH.ToHttpApiData a) =>
a ->
BCL.ByteString
toPath :: forall a. ToHttpApiData a => a -> ByteString
toPath = Builder -> ByteString
BB.toLazyByteString (Builder -> ByteString) -> (a -> Builder) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Builder
forall a. ToHttpApiData a => a -> Builder
WH.toEncodedUrlPiece
toHeader :: (WH.ToHttpApiData a) => (NH.HeaderName, a) -> [NH.Header]
(HeaderName, a)
x = [(a -> ByteString) -> (HeaderName, a) -> (HeaderName, ByteString)
forall a b. (a -> b) -> (HeaderName, a) -> (HeaderName, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> ByteString
forall a. ToHttpApiData a => a -> ByteString
WH.toHeader (HeaderName, a)
x]
toForm :: (WH.ToHttpApiData v) => (BC.ByteString, v) -> WH.Form
toForm :: forall v. ToHttpApiData v => (ByteString, v) -> Form
toForm (ByteString
k, v
v) = [(String, v)] -> Form
forall a. ToForm a => a -> Form
WH.toForm [(ByteString -> String
BC.unpack ByteString
k, v
v)]
toQuery :: (WH.ToHttpApiData a) => (BC.ByteString, Maybe a) -> [NH.QueryItem]
toQuery :: forall a. ToHttpApiData a => (ByteString, Maybe a) -> Query
toQuery (ByteString, Maybe a)
x = [((Maybe a -> Maybe ByteString)
-> (ByteString, Maybe a) -> (ByteString, Maybe ByteString)
forall a b. (a -> b) -> (ByteString, a) -> (ByteString, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe a -> Maybe ByteString)
-> (ByteString, Maybe a) -> (ByteString, Maybe ByteString))
-> ((a -> ByteString) -> Maybe a -> Maybe ByteString)
-> (a -> ByteString)
-> (ByteString, Maybe a)
-> (ByteString, Maybe ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> ByteString) -> Maybe a -> Maybe ByteString
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) a -> ByteString
toQueryParam (ByteString, Maybe a)
x]
where
toQueryParam :: a -> ByteString
toQueryParam = Text -> ByteString
T.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
WH.toQueryParam
toJsonQuery :: (A.ToJSON a) => (BC.ByteString, Maybe a) -> [NH.QueryItem]
toJsonQuery :: forall a. ToJSON a => (ByteString, Maybe a) -> Query
toJsonQuery = (ByteString, Maybe Text) -> Query
forall a. ToHttpApiData a => (ByteString, Maybe a) -> Query
toQuery ((ByteString, Maybe Text) -> Query)
-> ((ByteString, Maybe a) -> (ByteString, Maybe Text))
-> (ByteString, Maybe a)
-> Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Maybe a -> Maybe Text)
-> (ByteString, Maybe a) -> (ByteString, Maybe Text)
forall a b. (a -> b) -> (ByteString, a) -> (ByteString, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe a -> Maybe Text)
-> (ByteString, Maybe a) -> (ByteString, Maybe Text))
-> ((a -> Text) -> Maybe a -> Maybe Text)
-> (a -> Text)
-> (ByteString, Maybe a)
-> (ByteString, Maybe Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Text) -> Maybe a -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) (ByteString -> Text
TL.decodeUtf8 (ByteString -> Text) -> (a -> ByteString) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
forall a. ToJSON a => a -> ByteString
A.encode)
toPartialEscapeQuery :: B.ByteString -> NH.Query -> NH.PartialEscapeQuery
toPartialEscapeQuery :: ByteString -> Query -> PartialEscapeQuery
toPartialEscapeQuery ByteString
extraUnreserved Query
query = ((ByteString, Maybe ByteString) -> PartialEscapeQueryItem)
-> Query -> PartialEscapeQuery
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(ByteString
k, Maybe ByteString
v) -> (ByteString
k, [EscapeItem]
-> (ByteString -> [EscapeItem]) -> Maybe ByteString -> [EscapeItem]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] ByteString -> [EscapeItem]
go Maybe ByteString
v)) Query
query
where
go :: B.ByteString -> [NH.EscapeItem]
go :: ByteString -> [EscapeItem]
go ByteString
v =
ByteString
v
ByteString -> (ByteString -> [ByteString]) -> [ByteString]
forall a b. a -> (a -> b) -> b
& (Word8 -> Word8 -> Bool) -> ByteString -> [ByteString]
B.groupBy (\Word8
a Word8
b -> Word8
a Word8 -> ByteString -> Bool
`B.notElem` ByteString
extraUnreserved Bool -> Bool -> Bool
&& Word8
b Word8 -> ByteString -> Bool
`B.notElem` ByteString
extraUnreserved)
[ByteString] -> ([ByteString] -> [EscapeItem]) -> [EscapeItem]
forall a b. a -> (a -> b) -> b
& (ByteString -> EscapeItem) -> [ByteString] -> [EscapeItem]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
( \ByteString
xs ->
if ByteString -> Bool
B.null ByteString
xs
then ByteString -> EscapeItem
NH.QN ByteString
xs
else
if HasCallStack => ByteString -> Word8
ByteString -> Word8
B.head ByteString
xs Word8 -> ByteString -> Bool
`B.elem` ByteString
extraUnreserved
then ByteString -> EscapeItem
NH.QN ByteString
xs
else ByteString -> EscapeItem
NH.QE ByteString
xs
)
data CollectionFormat
=
CommaSeparated
|
SpaceSeparated
|
TabSeparated
|
PipeSeparated
|
MultiParamArray
toHeaderColl :: (WH.ToHttpApiData a) => CollectionFormat -> (NH.HeaderName, [a]) -> [NH.Header]
CollectionFormat
c (HeaderName, [a])
xs = CollectionFormat
-> ((HeaderName, a) -> RequestHeaders)
-> (HeaderName, [a])
-> RequestHeaders
forall (f :: * -> *) a b.
Traversable f =>
CollectionFormat
-> (f a -> [(b, ByteString)]) -> f [a] -> [(b, ByteString)]
_toColl CollectionFormat
c (HeaderName, a) -> RequestHeaders
forall a. ToHttpApiData a => (HeaderName, a) -> RequestHeaders
toHeader (HeaderName, [a])
xs
toFormColl :: (WH.ToHttpApiData v) => CollectionFormat -> (BC.ByteString, [v]) -> WH.Form
toFormColl :: forall v.
ToHttpApiData v =>
CollectionFormat -> (ByteString, [v]) -> Form
toFormColl CollectionFormat
c (ByteString, [v])
xs = [(String, String)] -> Form
forall a. ToForm a => a -> Form
WH.toForm ([(String, String)] -> Form) -> [(String, String)] -> Form
forall a b. (a -> b) -> a -> b
$ ((HeaderName, ByteString) -> (String, String))
-> RequestHeaders -> [(String, String)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (HeaderName, ByteString) -> (String, String)
unpack (RequestHeaders -> [(String, String)])
-> RequestHeaders -> [(String, String)]
forall a b. (a -> b) -> a -> b
$ CollectionFormat
-> ((HeaderName, v) -> RequestHeaders)
-> (HeaderName, [v])
-> RequestHeaders
forall (f :: * -> *) a b.
Traversable f =>
CollectionFormat
-> (f a -> [(b, ByteString)]) -> f [a] -> [(b, ByteString)]
_toColl CollectionFormat
c (HeaderName, v) -> RequestHeaders
forall a. ToHttpApiData a => (HeaderName, a) -> RequestHeaders
toHeader ((HeaderName, [v]) -> RequestHeaders)
-> (HeaderName, [v]) -> RequestHeaders
forall a b. (a -> b) -> a -> b
$ (ByteString, [v]) -> (HeaderName, [v])
forall {s} {b}. FoldCase s => (s, b) -> (CI s, b)
pack (ByteString, [v])
xs
where
pack :: (s, b) -> (CI s, b)
pack (s
k, b
v) = (s -> CI s
forall s. FoldCase s => s -> CI s
CI.mk s
k, b
v)
unpack :: (HeaderName, ByteString) -> (String, String)
unpack (HeaderName
k, ByteString
v) = (ByteString -> String
BC.unpack (HeaderName -> ByteString
forall s. CI s -> s
CI.original HeaderName
k), ByteString -> String
BC.unpack ByteString
v)
toQueryColl :: (WH.ToHttpApiData a) => CollectionFormat -> (BC.ByteString, Maybe [a]) -> NH.Query
toQueryColl :: forall a.
ToHttpApiData a =>
CollectionFormat -> (ByteString, Maybe [a]) -> Query
toQueryColl CollectionFormat
c (ByteString, Maybe [a])
xs = CollectionFormat
-> ((ByteString, Maybe a) -> Query)
-> (ByteString, Maybe [a])
-> Query
forall (f :: * -> *) (t :: * -> *) a b.
(Traversable f, Traversable t, Alternative t) =>
CollectionFormat
-> (f (t a) -> [(b, t ByteString)])
-> f (t [a])
-> [(b, t ByteString)]
_toCollA CollectionFormat
c (ByteString, Maybe a) -> Query
forall a. ToHttpApiData a => (ByteString, Maybe a) -> Query
toQuery (ByteString, Maybe [a])
xs
toJsonQueryColl :: (A.ToJSON a) => CollectionFormat -> (BC.ByteString, Maybe [a]) -> NH.Query
toJsonQueryColl :: forall a.
ToJSON a =>
CollectionFormat -> (ByteString, Maybe [a]) -> Query
toJsonQueryColl CollectionFormat
c (ByteString, Maybe [a])
xs = CollectionFormat
-> ((ByteString, Maybe a) -> Query)
-> (ByteString, Maybe [a])
-> Query
forall (f :: * -> *) (t :: * -> *) a b.
(Traversable f, Traversable t, Alternative t) =>
CollectionFormat
-> (f (t a) -> [(b, t ByteString)])
-> f (t [a])
-> [(b, t ByteString)]
_toCollA CollectionFormat
c (ByteString, Maybe a) -> Query
forall a. ToJSON a => (ByteString, Maybe a) -> Query
toJsonQuery (ByteString, Maybe [a])
xs
_toColl :: (P.Traversable f) => CollectionFormat -> (f a -> [(b, BC.ByteString)]) -> f [a] -> [(b, BC.ByteString)]
_toColl :: forall (f :: * -> *) a b.
Traversable f =>
CollectionFormat
-> (f a -> [(b, ByteString)]) -> f [a] -> [(b, ByteString)]
_toColl CollectionFormat
c f a -> [(b, ByteString)]
encode f [a]
xs = ((b, Maybe ByteString) -> (b, ByteString))
-> [(b, Maybe ByteString)] -> [(b, ByteString)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Maybe ByteString -> ByteString)
-> (b, Maybe ByteString) -> (b, ByteString)
forall a b. (a -> b) -> (b, a) -> (b, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe ByteString -> ByteString
forall a. HasCallStack => Maybe a -> a
P.fromJust) (CollectionFormat
-> (f (Maybe a) -> [(b, Maybe ByteString)])
-> (Char -> ByteString)
-> f (Maybe [a])
-> [(b, Maybe ByteString)]
forall c (f :: * -> *) (t :: * -> *) a b.
(Monoid c, Traversable f, Traversable t, Alternative t) =>
CollectionFormat
-> (f (t a) -> [(b, t c)])
-> (Char -> c)
-> f (t [a])
-> [(b, t c)]
_toCollA' CollectionFormat
c f (Maybe a) -> [(b, Maybe ByteString)]
fencode Char -> ByteString
BC.singleton (([a] -> Maybe [a]) -> f [a] -> f (Maybe [a])
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [a] -> Maybe [a]
forall a. a -> Maybe a
Just f [a]
xs))
where
fencode :: f (Maybe a) -> [(b, Maybe ByteString)]
fencode = ((b, ByteString) -> (b, Maybe ByteString))
-> [(b, ByteString)] -> [(b, Maybe ByteString)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ByteString -> Maybe ByteString)
-> (b, ByteString) -> (b, Maybe ByteString)
forall a b. (a -> b) -> (b, a) -> (b, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just) ([(b, ByteString)] -> [(b, Maybe ByteString)])
-> (f (Maybe a) -> [(b, ByteString)])
-> f (Maybe a)
-> [(b, Maybe ByteString)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> [(b, ByteString)]
encode (f a -> [(b, ByteString)])
-> (f (Maybe a) -> f a) -> f (Maybe a) -> [(b, ByteString)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe a -> a) -> f (Maybe a) -> f a
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe a -> a
forall a. HasCallStack => Maybe a -> a
P.fromJust
{-# INLINE fencode #-}
_toCollA :: (P.Traversable f, P.Traversable t, P.Alternative t) => CollectionFormat -> (f (t a) -> [(b, t BC.ByteString)]) -> f (t [a]) -> [(b, t BC.ByteString)]
_toCollA :: forall (f :: * -> *) (t :: * -> *) a b.
(Traversable f, Traversable t, Alternative t) =>
CollectionFormat
-> (f (t a) -> [(b, t ByteString)])
-> f (t [a])
-> [(b, t ByteString)]
_toCollA CollectionFormat
c f (t a) -> [(b, t ByteString)]
encode f (t [a])
xs = CollectionFormat
-> (f (t a) -> [(b, t ByteString)])
-> (Char -> ByteString)
-> f (t [a])
-> [(b, t ByteString)]
forall c (f :: * -> *) (t :: * -> *) a b.
(Monoid c, Traversable f, Traversable t, Alternative t) =>
CollectionFormat
-> (f (t a) -> [(b, t c)])
-> (Char -> c)
-> f (t [a])
-> [(b, t c)]
_toCollA' CollectionFormat
c f (t a) -> [(b, t ByteString)]
encode Char -> ByteString
BC.singleton f (t [a])
xs
_toCollA' :: (P.Monoid c, P.Traversable f, P.Traversable t, P.Alternative t) => CollectionFormat -> (f (t a) -> [(b, t c)]) -> (Char -> c) -> f (t [a]) -> [(b, t c)]
_toCollA' :: forall c (f :: * -> *) (t :: * -> *) a b.
(Monoid c, Traversable f, Traversable t, Alternative t) =>
CollectionFormat
-> (f (t a) -> [(b, t c)])
-> (Char -> c)
-> f (t [a])
-> [(b, t c)]
_toCollA' CollectionFormat
c f (t a) -> [(b, t c)]
encode Char -> c
one f (t [a])
xs = case CollectionFormat
c of
CollectionFormat
CommaSeparated -> c -> [(b, t c)]
go (Char -> c
one Char
',')
CollectionFormat
SpaceSeparated -> c -> [(b, t c)]
go (Char -> c
one Char
' ')
CollectionFormat
TabSeparated -> c -> [(b, t c)]
go (Char -> c
one Char
'\t')
CollectionFormat
PipeSeparated -> c -> [(b, t c)]
go (Char -> c
one Char
'|')
CollectionFormat
MultiParamArray -> [(b, t c)]
expandList
where
go :: c -> [(b, t c)]
go c
sep =
[((b, t c) -> (b, t c) -> (b, t c)) -> [(b, t c)] -> (b, t c)
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
P.foldl1 (\(b
sk, t c
sv) (b
_, t c
v) -> (b
sk, (c -> c -> c -> c
forall {a}. Semigroup a => a -> a -> a -> a
combine c
sep (c -> c -> c) -> t c -> t (c -> c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> t c
sv t (c -> c) -> t c -> t c
forall a b. t (a -> b) -> t a -> t b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> t c
v) t c -> t c -> t c
forall a. t a -> t a -> t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> t c
sv t c -> t c -> t c
forall a. t a -> t a -> t a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> t c
v)) [(b, t c)]
expandList]
combine :: a -> a -> a -> a
combine a
sep a
x a
y = a
x a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
sep a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
y
expandList :: [(b, t c)]
expandList = ((f (t a) -> [(b, t c)]) -> [f (t a)] -> [(b, t c)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
P.concatMap f (t a) -> [(b, t c)]
encode ([f (t a)] -> [(b, t c)])
-> (f (t [a]) -> [f (t a)]) -> f (t [a]) -> [(b, t c)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((t [a] -> [t a]) -> f (t [a]) -> [f (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) -> f a -> f (f b)
P.traverse ((t [a] -> [t a]) -> f (t [a]) -> [f (t a)])
-> (([a] -> [a]) -> t [a] -> [t a])
-> ([a] -> [a])
-> f (t [a])
-> [f (t a)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([a] -> [a]) -> t [a] -> [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)
P.traverse) [a] -> [a]
forall a. [a] -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
P.toList) f (t [a])
xs
{-# INLINE go #-}
{-# INLINE expandList #-}
{-# INLINE combine #-}
class
(P.Typeable a) =>
AuthMethod a
where
applyAuthMethod ::
GenAIClientConfig ->
a ->
ClientRequest req contentType res accept ->
IO (ClientRequest req contentType res accept)
data AnyAuthMethod = forall a. (AuthMethod a) => AnyAuthMethod a deriving (P.Typeable)
instance AuthMethod AnyAuthMethod where applyAuthMethod :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
GenAIClientConfig
-> AnyAuthMethod
-> ClientRequest req contentType res accept
-> IO (ClientRequest req contentType res accept)
applyAuthMethod GenAIClientConfig
config (AnyAuthMethod a
a) ClientRequest req contentType res accept
req = GenAIClientConfig
-> a
-> ClientRequest req contentType res accept
-> IO (ClientRequest req contentType res accept)
forall a {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
AuthMethod a =>
GenAIClientConfig
-> a
-> ClientRequest req contentType res accept
-> IO (ClientRequest req contentType res accept)
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
GenAIClientConfig
-> a
-> ClientRequest req contentType res accept
-> IO (ClientRequest req contentType res accept)
applyAuthMethod GenAIClientConfig
config a
a ClientRequest req contentType res accept
req
data AuthMethodException = AuthMethodException String deriving (Int -> AuthMethodException -> ShowS
[AuthMethodException] -> ShowS
AuthMethodException -> String
(Int -> AuthMethodException -> ShowS)
-> (AuthMethodException -> String)
-> ([AuthMethodException] -> ShowS)
-> Show AuthMethodException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AuthMethodException -> ShowS
showsPrec :: Int -> AuthMethodException -> ShowS
$cshow :: AuthMethodException -> String
show :: AuthMethodException -> String
$cshowList :: [AuthMethodException] -> ShowS
showList :: [AuthMethodException] -> ShowS
P.Show, P.Typeable)
instance E.Exception AuthMethodException
_applyAuthMethods ::
ClientRequest req contentType res accept ->
GenAIClientConfig ->
IO (ClientRequest req contentType res accept)
_applyAuthMethods :: forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
ClientRequest req contentType res accept
-> GenAIClientConfig
-> IO (ClientRequest req contentType res accept)
_applyAuthMethods ClientRequest req contentType res accept
req config :: GenAIClientConfig
config@(GenAIClientConfig {configAuthMethods :: GenAIClientConfig -> [AnyAuthMethod]
configAuthMethods = [AnyAuthMethod]
as}) =
(ClientRequest req contentType res accept
-> AnyAuthMethod -> IO (ClientRequest req contentType res accept))
-> ClientRequest req contentType res accept
-> [AnyAuthMethod]
-> IO (ClientRequest req contentType res accept)
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldlM ClientRequest req contentType res accept
-> AnyAuthMethod -> IO (ClientRequest req contentType res accept)
go ClientRequest req contentType res accept
req [AnyAuthMethod]
as
where
go :: ClientRequest req contentType res accept
-> AnyAuthMethod -> IO (ClientRequest req contentType res accept)
go ClientRequest req contentType res accept
r (AnyAuthMethod a
a) = GenAIClientConfig
-> a
-> ClientRequest req contentType res accept
-> IO (ClientRequest req contentType res accept)
forall a {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
AuthMethod a =>
GenAIClientConfig
-> a
-> ClientRequest req contentType res accept
-> IO (ClientRequest req contentType res accept)
forall {k} {k} {k} {k} (req :: k) (contentType :: k) (res :: k)
(accept :: k).
GenAIClientConfig
-> a
-> ClientRequest req contentType res accept
-> IO (ClientRequest req contentType res accept)
applyAuthMethod GenAIClientConfig
config a
a ClientRequest req contentType res accept
r
#if MIN_VERSION_aeson(2,0,0)
_omitNulls :: [(A.Key, A.Value)] -> A.Value
#else
_omitNulls :: [(Text, A.Value)] -> A.Value
#endif
_omitNulls :: [(Key, Value)] -> Value
_omitNulls = [(Key, Value)] -> Value
A.object ([(Key, Value)] -> Value)
-> ([(Key, Value)] -> [(Key, Value)]) -> [(Key, Value)] -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Key, Value) -> Bool) -> [(Key, Value)] -> [(Key, Value)]
forall a. (a -> Bool) -> [a] -> [a]
P.filter (Key, Value) -> Bool
forall {a}. (a, Value) -> Bool
notNull
where
notNull :: (a, Value) -> Bool
notNull (a
_, Value
A.Null) = Bool
False
notNull (a, Value)
_ = Bool
True
_toFormItem :: (WH.ToHttpApiData a, Functor f) => t -> f a -> f (t, [Text])
_toFormItem :: forall a (f :: * -> *) t.
(ToHttpApiData a, Functor f) =>
t -> f a -> f (t, [Text])
_toFormItem t
name f a
x = (t
name,) ([Text] -> (t, [Text])) -> (a -> [Text]) -> a -> (t, [Text])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: []) (Text -> [Text]) -> (a -> Text) -> a -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. ToHttpApiData a => a -> Text
WH.toQueryParam (a -> (t, [Text])) -> f a -> f (t, [Text])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f a
x
_emptyToNothing :: Maybe String -> Maybe String
_emptyToNothing :: Maybe String -> Maybe String
_emptyToNothing (Just String
"") = Maybe String
forall a. Maybe a
Nothing
_emptyToNothing Maybe String
x = Maybe String
x
{-# INLINE _emptyToNothing #-}
_memptyToNothing :: (P.Monoid a, P.Eq a) => Maybe a -> Maybe a
_memptyToNothing :: forall a. (Monoid a, Eq a) => Maybe a -> Maybe a
_memptyToNothing (Just a
x) | a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
P.== a
forall a. Monoid a => a
P.mempty = Maybe a
forall a. Maybe a
Nothing
_memptyToNothing Maybe a
x = Maybe a
x
{-# INLINE _memptyToNothing #-}
newtype DateTime = DateTime {DateTime -> UTCTime
unDateTime :: TI.UTCTime}
deriving (DateTime -> DateTime -> Bool
(DateTime -> DateTime -> Bool)
-> (DateTime -> DateTime -> Bool) -> Eq DateTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DateTime -> DateTime -> Bool
== :: DateTime -> DateTime -> Bool
$c/= :: DateTime -> DateTime -> Bool
/= :: DateTime -> DateTime -> Bool
P.Eq, Typeable DateTime
Typeable DateTime =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DateTime -> c DateTime)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DateTime)
-> (DateTime -> Constr)
-> (DateTime -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DateTime))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateTime))
-> ((forall b. Data b => b -> b) -> DateTime -> DateTime)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r)
-> (forall u. (forall d. Data d => d -> u) -> DateTime -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> DateTime -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime)
-> Data DateTime
DateTime -> Constr
DateTime -> DataType
(forall b. Data b => b -> b) -> DateTime -> DateTime
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) -> DateTime -> u
forall u. (forall d. Data d => d -> u) -> DateTime -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DateTime
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DateTime -> c DateTime
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DateTime)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateTime)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DateTime -> c DateTime
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DateTime -> c DateTime
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DateTime
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DateTime
$ctoConstr :: DateTime -> Constr
toConstr :: DateTime -> Constr
$cdataTypeOf :: DateTime -> DataType
dataTypeOf :: DateTime -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DateTime)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DateTime)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateTime)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateTime)
$cgmapT :: (forall b. Data b => b -> b) -> DateTime -> DateTime
gmapT :: (forall b. Data b => b -> b) -> DateTime -> DateTime
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DateTime -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DateTime -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> DateTime -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DateTime -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DateTime -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DateTime -> m DateTime
P.Data, Eq DateTime
Eq DateTime =>
(DateTime -> DateTime -> Ordering)
-> (DateTime -> DateTime -> Bool)
-> (DateTime -> DateTime -> Bool)
-> (DateTime -> DateTime -> Bool)
-> (DateTime -> DateTime -> Bool)
-> (DateTime -> DateTime -> DateTime)
-> (DateTime -> DateTime -> DateTime)
-> Ord DateTime
DateTime -> DateTime -> Bool
DateTime -> DateTime -> Ordering
DateTime -> DateTime -> DateTime
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
$ccompare :: DateTime -> DateTime -> Ordering
compare :: DateTime -> DateTime -> Ordering
$c< :: DateTime -> DateTime -> Bool
< :: DateTime -> DateTime -> Bool
$c<= :: DateTime -> DateTime -> Bool
<= :: DateTime -> DateTime -> Bool
$c> :: DateTime -> DateTime -> Bool
> :: DateTime -> DateTime -> Bool
$c>= :: DateTime -> DateTime -> Bool
>= :: DateTime -> DateTime -> Bool
$cmax :: DateTime -> DateTime -> DateTime
max :: DateTime -> DateTime -> DateTime
$cmin :: DateTime -> DateTime -> DateTime
min :: DateTime -> DateTime -> DateTime
P.Ord, P.Typeable, DateTime -> ()
(DateTime -> ()) -> NFData DateTime
forall a. (a -> ()) -> NFData a
$crnf :: DateTime -> ()
rnf :: DateTime -> ()
NF.NFData)
instance A.FromJSON DateTime where
parseJSON :: Value -> Parser DateTime
parseJSON = String -> (Text -> Parser DateTime) -> Value -> Parser DateTime
forall a. String -> (Text -> Parser a) -> Value -> Parser a
A.withText String
"DateTime" (String -> Parser DateTime
forall (m :: * -> *).
(MonadFail m, Alternative m) =>
String -> m DateTime
_readDateTime (String -> Parser DateTime)
-> (Text -> String) -> Text -> Parser DateTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack)
instance A.ToJSON DateTime where
toJSON :: DateTime -> Value
toJSON (DateTime UTCTime
t) = String -> Value
forall a. ToJSON a => a -> Value
A.toJSON (UTCTime -> String
forall t. (t ~ UTCTime, FormatTime t) => t -> String
_showDateTime UTCTime
t)
instance WH.FromHttpApiData DateTime where
parseUrlPiece :: Text -> Either Text DateTime
parseUrlPiece = Either Text DateTime
-> (DateTime -> Either Text DateTime)
-> Maybe DateTime
-> Either Text DateTime
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Text -> Either Text DateTime
forall a b. a -> Either a b
P.Left Text
"parseUrlPiece @DateTime") DateTime -> Either Text DateTime
forall a b. b -> Either a b
P.Right (Maybe DateTime -> Either Text DateTime)
-> (Text -> Maybe DateTime) -> Text -> Either Text DateTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe DateTime
forall (m :: * -> *).
(MonadFail m, Alternative m) =>
String -> m DateTime
_readDateTime (String -> Maybe DateTime)
-> (Text -> String) -> Text -> Maybe DateTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
instance WH.ToHttpApiData DateTime where
toUrlPiece :: DateTime -> Text
toUrlPiece (DateTime UTCTime
t) = String -> Text
T.pack (UTCTime -> String
forall t. (t ~ UTCTime, FormatTime t) => t -> String
_showDateTime UTCTime
t)
instance P.Show DateTime where
show :: DateTime -> String
show (DateTime UTCTime
t) = UTCTime -> String
forall t. (t ~ UTCTime, FormatTime t) => t -> String
_showDateTime UTCTime
t
instance MimeRender MimeMultipartFormData DateTime where
mimeRender :: Proxy MimeMultipartFormData -> DateTime -> ByteString
mimeRender Proxy MimeMultipartFormData
_ = DateTime -> ByteString
forall a. ToHttpApiData a => a -> ByteString
mimeRenderDefaultMultipartFormData
_readDateTime :: (MonadFail m, Alternative m) => String -> m DateTime
_readDateTime :: forall (m :: * -> *).
(MonadFail m, Alternative m) =>
String -> m DateTime
_readDateTime String
s =
UTCTime -> DateTime
DateTime (UTCTime -> DateTime) -> m UTCTime -> m DateTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> m UTCTime
forall t (m :: * -> *).
(ParseTime t, MonadFail m, Alternative m) =>
String -> m t
_parseISO8601 String
s
{-# INLINE _readDateTime #-}
_showDateTime :: (t ~ TI.UTCTime, TI.FormatTime t) => t -> String
_showDateTime :: forall t. (t ~ UTCTime, FormatTime t) => t -> String
_showDateTime =
t -> String
UTCTime -> String
TI.formatISO8601Millis
{-# INLINE _showDateTime #-}
_parseISO8601 :: (TI.ParseTime t, MonadFail m, Alternative m) => String -> m t
_parseISO8601 :: forall t (m :: * -> *).
(ParseTime t, MonadFail m, Alternative m) =>
String -> m t
_parseISO8601 String
t =
[m t] -> m t
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
P.asum ([m t] -> m t) -> [m t] -> m t
forall a b. (a -> b) -> a -> b
$
(String -> String -> m t) -> String -> String -> m t
forall a b c. (a -> b -> c) -> b -> a -> c
P.flip (Bool -> TimeLocale -> String -> String -> m t
forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> String -> String -> m t
TI.parseTimeM Bool
True TimeLocale
TI.defaultTimeLocale) String
t
(String -> m t) -> [String] -> [m t]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [String
"%FT%T%QZ", String
"%FT%T%Q%z", String
"%FT%T%Q%Z"]
{-# INLINE _parseISO8601 #-}
newtype Date = Date {Date -> Day
unDate :: TI.Day}
deriving (Int -> Date
Date -> Int
Date -> [Date]
Date -> Date
Date -> Date -> [Date]
Date -> Date -> Date -> [Date]
(Date -> Date)
-> (Date -> Date)
-> (Int -> Date)
-> (Date -> Int)
-> (Date -> [Date])
-> (Date -> Date -> [Date])
-> (Date -> Date -> [Date])
-> (Date -> Date -> Date -> [Date])
-> Enum Date
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Date -> Date
succ :: Date -> Date
$cpred :: Date -> Date
pred :: Date -> Date
$ctoEnum :: Int -> Date
toEnum :: Int -> Date
$cfromEnum :: Date -> Int
fromEnum :: Date -> Int
$cenumFrom :: Date -> [Date]
enumFrom :: Date -> [Date]
$cenumFromThen :: Date -> Date -> [Date]
enumFromThen :: Date -> Date -> [Date]
$cenumFromTo :: Date -> Date -> [Date]
enumFromTo :: Date -> Date -> [Date]
$cenumFromThenTo :: Date -> Date -> Date -> [Date]
enumFromThenTo :: Date -> Date -> Date -> [Date]
P.Enum, Date -> Date -> Bool
(Date -> Date -> Bool) -> (Date -> Date -> Bool) -> Eq Date
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Date -> Date -> Bool
== :: Date -> Date -> Bool
$c/= :: Date -> Date -> Bool
/= :: Date -> Date -> Bool
P.Eq, Typeable Date
Typeable Date =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Date -> c Date)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Date)
-> (Date -> Constr)
-> (Date -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Date))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Date))
-> ((forall b. Data b => b -> b) -> Date -> Date)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r)
-> (forall u. (forall d. Data d => d -> u) -> Date -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Date -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Date -> m Date)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Date -> m Date)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Date -> m Date)
-> Data Date
Date -> Constr
Date -> DataType
(forall b. Data b => b -> b) -> Date -> Date
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) -> Date -> u
forall u. (forall d. Data d => d -> u) -> Date -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Date -> m Date
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Date -> m Date
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Date
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Date -> c Date
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Date)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Date)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Date -> c Date
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Date -> c Date
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Date
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Date
$ctoConstr :: Date -> Constr
toConstr :: Date -> Constr
$cdataTypeOf :: Date -> DataType
dataTypeOf :: Date -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Date)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Date)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Date)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Date)
$cgmapT :: (forall b. Data b => b -> b) -> Date -> Date
gmapT :: (forall b. Data b => b -> b) -> Date -> Date
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Date -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Date -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Date -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Date -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Date -> m Date
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Date -> m Date
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Date -> m Date
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Date -> m Date
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Date -> m Date
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Date -> m Date
P.Data, Eq Date
Eq Date =>
(Date -> Date -> Ordering)
-> (Date -> Date -> Bool)
-> (Date -> Date -> Bool)
-> (Date -> Date -> Bool)
-> (Date -> Date -> Bool)
-> (Date -> Date -> Date)
-> (Date -> Date -> Date)
-> Ord Date
Date -> Date -> Bool
Date -> Date -> Ordering
Date -> Date -> Date
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
$ccompare :: Date -> Date -> Ordering
compare :: Date -> Date -> Ordering
$c< :: Date -> Date -> Bool
< :: Date -> Date -> Bool
$c<= :: Date -> Date -> Bool
<= :: Date -> Date -> Bool
$c> :: Date -> Date -> Bool
> :: Date -> Date -> Bool
$c>= :: Date -> Date -> Bool
>= :: Date -> Date -> Bool
$cmax :: Date -> Date -> Date
max :: Date -> Date -> Date
$cmin :: Date -> Date -> Date
min :: Date -> Date -> Date
P.Ord, Ord Date
Ord Date =>
((Date, Date) -> [Date])
-> ((Date, Date) -> Date -> Int)
-> ((Date, Date) -> Date -> Int)
-> ((Date, Date) -> Date -> Bool)
-> ((Date, Date) -> Int)
-> ((Date, Date) -> Int)
-> Ix Date
(Date, Date) -> Int
(Date, Date) -> [Date]
(Date, Date) -> Date -> Bool
(Date, Date) -> Date -> Int
forall a.
Ord a =>
((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
$crange :: (Date, Date) -> [Date]
range :: (Date, Date) -> [Date]
$cindex :: (Date, Date) -> Date -> Int
index :: (Date, Date) -> Date -> Int
$cunsafeIndex :: (Date, Date) -> Date -> Int
unsafeIndex :: (Date, Date) -> Date -> Int
$cinRange :: (Date, Date) -> Date -> Bool
inRange :: (Date, Date) -> Date -> Bool
$crangeSize :: (Date, Date) -> Int
rangeSize :: (Date, Date) -> Int
$cunsafeRangeSize :: (Date, Date) -> Int
unsafeRangeSize :: (Date, Date) -> Int
P.Ix, Date -> ()
(Date -> ()) -> NFData Date
forall a. (a -> ()) -> NFData a
$crnf :: Date -> ()
rnf :: Date -> ()
NF.NFData)
instance A.FromJSON Date where
parseJSON :: Value -> Parser Date
parseJSON = String -> (Text -> Parser Date) -> Value -> Parser Date
forall a. String -> (Text -> Parser a) -> Value -> Parser a
A.withText String
"Date" (String -> Parser Date
forall (m :: * -> *). MonadFail m => String -> m Date
_readDate (String -> Parser Date) -> (Text -> String) -> Text -> Parser Date
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack)
instance A.ToJSON Date where
toJSON :: Date -> Value
toJSON (Date Day
t) = String -> Value
forall a. ToJSON a => a -> Value
A.toJSON (Day -> String
forall t. FormatTime t => t -> String
_showDate Day
t)
instance WH.FromHttpApiData Date where
parseUrlPiece :: Text -> Either Text Date
parseUrlPiece = Either Text Date
-> (Date -> Either Text Date) -> Maybe Date -> Either Text Date
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Text -> Either Text Date
forall a b. a -> Either a b
P.Left Text
"parseUrlPiece @Date") Date -> Either Text Date
forall a b. b -> Either a b
P.Right (Maybe Date -> Either Text Date)
-> (Text -> Maybe Date) -> Text -> Either Text Date
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Date
forall (m :: * -> *). MonadFail m => String -> m Date
_readDate (String -> Maybe Date) -> (Text -> String) -> Text -> Maybe Date
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
instance WH.ToHttpApiData Date where
toUrlPiece :: Date -> Text
toUrlPiece (Date Day
t) = String -> Text
T.pack (Day -> String
forall t. FormatTime t => t -> String
_showDate Day
t)
instance P.Show Date where
show :: Date -> String
show (Date Day
t) = Day -> String
forall t. FormatTime t => t -> String
_showDate Day
t
instance MimeRender MimeMultipartFormData Date where
mimeRender :: Proxy MimeMultipartFormData -> Date -> ByteString
mimeRender Proxy MimeMultipartFormData
_ = Date -> ByteString
forall a. ToHttpApiData a => a -> ByteString
mimeRenderDefaultMultipartFormData
_readDate :: (MonadFail m) => String -> m Date
_readDate :: forall (m :: * -> *). MonadFail m => String -> m Date
_readDate String
s = Day -> Date
Date (Day -> Date) -> m Day -> m Date
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> TimeLocale -> String -> String -> m Day
forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> String -> String -> m t
TI.parseTimeM Bool
True TimeLocale
TI.defaultTimeLocale String
"%Y-%m-%d" String
s
{-# INLINE _readDate #-}
_showDate :: (TI.FormatTime t) => t -> String
_showDate :: forall t. FormatTime t => t -> String
_showDate =
TimeLocale -> String -> t -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
TI.formatTime TimeLocale
TI.defaultTimeLocale String
"%Y-%m-%d"
{-# INLINE _showDate #-}
newtype ByteArray = ByteArray {ByteArray -> ByteString
unByteArray :: BL.ByteString}
deriving (ByteArray -> ByteArray -> Bool
(ByteArray -> ByteArray -> Bool)
-> (ByteArray -> ByteArray -> Bool) -> Eq ByteArray
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ByteArray -> ByteArray -> Bool
== :: ByteArray -> ByteArray -> Bool
$c/= :: ByteArray -> ByteArray -> Bool
/= :: ByteArray -> ByteArray -> Bool
P.Eq, Typeable ByteArray
Typeable ByteArray =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ByteArray -> c ByteArray)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ByteArray)
-> (ByteArray -> Constr)
-> (ByteArray -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ByteArray))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteArray))
-> ((forall b. Data b => b -> b) -> ByteArray -> ByteArray)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r)
-> (forall u. (forall d. Data d => d -> u) -> ByteArray -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ByteArray -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray)
-> Data ByteArray
ByteArray -> Constr
ByteArray -> DataType
(forall b. Data b => b -> b) -> ByteArray -> ByteArray
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) -> ByteArray -> u
forall u. (forall d. Data d => d -> u) -> ByteArray -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ByteArray
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ByteArray -> c ByteArray
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ByteArray)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteArray)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ByteArray -> c ByteArray
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ByteArray -> c ByteArray
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ByteArray
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ByteArray
$ctoConstr :: ByteArray -> Constr
toConstr :: ByteArray -> Constr
$cdataTypeOf :: ByteArray -> DataType
dataTypeOf :: ByteArray -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ByteArray)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ByteArray)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteArray)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteArray)
$cgmapT :: (forall b. Data b => b -> b) -> ByteArray -> ByteArray
gmapT :: (forall b. Data b => b -> b) -> ByteArray -> ByteArray
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ByteArray -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ByteArray -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ByteArray -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ByteArray -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ByteArray -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ByteArray -> m ByteArray
P.Data, Eq ByteArray
Eq ByteArray =>
(ByteArray -> ByteArray -> Ordering)
-> (ByteArray -> ByteArray -> Bool)
-> (ByteArray -> ByteArray -> Bool)
-> (ByteArray -> ByteArray -> Bool)
-> (ByteArray -> ByteArray -> Bool)
-> (ByteArray -> ByteArray -> ByteArray)
-> (ByteArray -> ByteArray -> ByteArray)
-> Ord ByteArray
ByteArray -> ByteArray -> Bool
ByteArray -> ByteArray -> Ordering
ByteArray -> ByteArray -> ByteArray
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
$ccompare :: ByteArray -> ByteArray -> Ordering
compare :: ByteArray -> ByteArray -> Ordering
$c< :: ByteArray -> ByteArray -> Bool
< :: ByteArray -> ByteArray -> Bool
$c<= :: ByteArray -> ByteArray -> Bool
<= :: ByteArray -> ByteArray -> Bool
$c> :: ByteArray -> ByteArray -> Bool
> :: ByteArray -> ByteArray -> Bool
$c>= :: ByteArray -> ByteArray -> Bool
>= :: ByteArray -> ByteArray -> Bool
$cmax :: ByteArray -> ByteArray -> ByteArray
max :: ByteArray -> ByteArray -> ByteArray
$cmin :: ByteArray -> ByteArray -> ByteArray
min :: ByteArray -> ByteArray -> ByteArray
P.Ord, P.Typeable, ByteArray -> ()
(ByteArray -> ()) -> NFData ByteArray
forall a. (a -> ()) -> NFData a
$crnf :: ByteArray -> ()
rnf :: ByteArray -> ()
NF.NFData)
instance A.FromJSON ByteArray where
parseJSON :: Value -> Parser ByteArray
parseJSON = String -> (Text -> Parser ByteArray) -> Value -> Parser ByteArray
forall a. String -> (Text -> Parser a) -> Value -> Parser a
A.withText String
"ByteArray" Text -> Parser ByteArray
forall (m :: * -> *). MonadFail m => Text -> m ByteArray
_readByteArray
instance A.ToJSON ByteArray where
toJSON :: ByteArray -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
A.toJSON (Text -> Value) -> (ByteArray -> Text) -> ByteArray -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteArray -> Text
_showByteArray
instance WH.FromHttpApiData ByteArray where
parseUrlPiece :: Text -> Either Text ByteArray
parseUrlPiece = Either Text ByteArray
-> (ByteArray -> Either Text ByteArray)
-> Maybe ByteArray
-> Either Text ByteArray
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Text -> Either Text ByteArray
forall a b. a -> Either a b
P.Left Text
"parseUrlPiece @ByteArray") ByteArray -> Either Text ByteArray
forall a b. b -> Either a b
P.Right (Maybe ByteArray -> Either Text ByteArray)
-> (Text -> Maybe ByteArray) -> Text -> Either Text ByteArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe ByteArray
forall (m :: * -> *). MonadFail m => Text -> m ByteArray
_readByteArray
instance WH.ToHttpApiData ByteArray where
toUrlPiece :: ByteArray -> Text
toUrlPiece = ByteArray -> Text
_showByteArray
instance P.Show ByteArray where
show :: ByteArray -> String
show = Text -> String
T.unpack (Text -> String) -> (ByteArray -> Text) -> ByteArray -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteArray -> Text
_showByteArray
instance MimeRender MimeMultipartFormData ByteArray where
mimeRender :: Proxy MimeMultipartFormData -> ByteArray -> ByteString
mimeRender Proxy MimeMultipartFormData
_ = ByteArray -> ByteString
forall a. ToHttpApiData a => a -> ByteString
mimeRenderDefaultMultipartFormData
_readByteArray :: (MonadFail m) => Text -> m ByteArray
_readByteArray :: forall (m :: * -> *). MonadFail m => Text -> m ByteArray
_readByteArray = (String -> m ByteArray)
-> (ByteString -> m ByteArray)
-> Either String ByteString
-> m ByteArray
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
P.either String -> m ByteArray
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
P.fail (ByteArray -> m ByteArray
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteArray -> m ByteArray)
-> (ByteString -> ByteArray) -> ByteString -> m ByteArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteArray
ByteArray) (Either String ByteString -> m ByteArray)
-> (Text -> Either String ByteString) -> Text -> m ByteArray
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String ByteString
BL64.decode (ByteString -> Either String ByteString)
-> (Text -> ByteString) -> Text -> Either String ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL.fromStrict (ByteString -> ByteString)
-> (Text -> ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8
{-# INLINE _readByteArray #-}
_showByteArray :: ByteArray -> Text
_showByteArray :: ByteArray -> Text
_showByteArray = ByteString -> Text
T.decodeUtf8 (ByteString -> Text)
-> (ByteArray -> ByteString) -> ByteArray -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL.toStrict (ByteString -> ByteString)
-> (ByteArray -> ByteString) -> ByteArray -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL64.encode (ByteString -> ByteString)
-> (ByteArray -> ByteString) -> ByteArray -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteArray -> ByteString
unByteArray
{-# INLINE _showByteArray #-}
newtype Binary = Binary {Binary -> ByteString
unBinary :: BL.ByteString}
deriving (Binary -> Binary -> Bool
(Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool) -> Eq Binary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Binary -> Binary -> Bool
== :: Binary -> Binary -> Bool
$c/= :: Binary -> Binary -> Bool
/= :: Binary -> Binary -> Bool
P.Eq, Typeable Binary
Typeable Binary =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binary -> c Binary)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Binary)
-> (Binary -> Constr)
-> (Binary -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Binary))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binary))
-> ((forall b. Data b => b -> b) -> Binary -> Binary)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Binary -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Binary -> r)
-> (forall u. (forall d. Data d => d -> u) -> Binary -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Binary -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary)
-> Data Binary
Binary -> Constr
Binary -> DataType
(forall b. Data b => b -> b) -> Binary -> Binary
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) -> Binary -> u
forall u. (forall d. Data d => d -> u) -> Binary -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Binary
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binary -> c Binary
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Binary)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binary)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binary -> c Binary
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binary -> c Binary
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Binary
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Binary
$ctoConstr :: Binary -> Constr
toConstr :: Binary -> Constr
$cdataTypeOf :: Binary -> DataType
dataTypeOf :: Binary -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Binary)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Binary)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binary)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binary)
$cgmapT :: (forall b. Data b => b -> b) -> Binary -> Binary
gmapT :: (forall b. Data b => b -> b) -> Binary -> Binary
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Binary -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Binary -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Binary -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Binary -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binary -> m Binary
P.Data, Eq Binary
Eq Binary =>
(Binary -> Binary -> Ordering)
-> (Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool)
-> (Binary -> Binary -> Bool)
-> (Binary -> Binary -> Binary)
-> (Binary -> Binary -> Binary)
-> Ord Binary
Binary -> Binary -> Bool
Binary -> Binary -> Ordering
Binary -> Binary -> Binary
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
$ccompare :: Binary -> Binary -> Ordering
compare :: Binary -> Binary -> Ordering
$c< :: Binary -> Binary -> Bool
< :: Binary -> Binary -> Bool
$c<= :: Binary -> Binary -> Bool
<= :: Binary -> Binary -> Bool
$c> :: Binary -> Binary -> Bool
> :: Binary -> Binary -> Bool
$c>= :: Binary -> Binary -> Bool
>= :: Binary -> Binary -> Bool
$cmax :: Binary -> Binary -> Binary
max :: Binary -> Binary -> Binary
$cmin :: Binary -> Binary -> Binary
min :: Binary -> Binary -> Binary
P.Ord, P.Typeable, Binary -> ()
(Binary -> ()) -> NFData Binary
forall a. (a -> ()) -> NFData a
$crnf :: Binary -> ()
rnf :: Binary -> ()
NF.NFData)
instance A.FromJSON Binary where
parseJSON :: Value -> Parser Binary
parseJSON = String -> (Text -> Parser Binary) -> Value -> Parser Binary
forall a. String -> (Text -> Parser a) -> Value -> Parser a
A.withText String
"Binary" Text -> Parser Binary
forall (m :: * -> *). MonadFail m => Text -> m Binary
_readBinaryBase64
instance A.ToJSON Binary where
toJSON :: Binary -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
A.toJSON (Text -> Value) -> (Binary -> Text) -> Binary -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary -> Text
_showBinaryBase64
instance WH.FromHttpApiData Binary where
parseUrlPiece :: Text -> Either Text Binary
parseUrlPiece = Either Text Binary
-> (Binary -> Either Text Binary)
-> Maybe Binary
-> Either Text Binary
forall b a. b -> (a -> b) -> Maybe a -> b
P.maybe (Text -> Either Text Binary
forall a b. a -> Either a b
P.Left Text
"parseUrlPiece @Binary") Binary -> Either Text Binary
forall a b. b -> Either a b
P.Right (Maybe Binary -> Either Text Binary)
-> (Text -> Maybe Binary) -> Text -> Either Text Binary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Binary
forall (m :: * -> *). MonadFail m => Text -> m Binary
_readBinaryBase64
instance WH.ToHttpApiData Binary where
toUrlPiece :: Binary -> Text
toUrlPiece = Binary -> Text
_showBinaryBase64
instance P.Show Binary where
show :: Binary -> String
show = Text -> String
T.unpack (Text -> String) -> (Binary -> Text) -> Binary -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary -> Text
_showBinaryBase64
instance MimeRender MimeMultipartFormData Binary where
mimeRender :: Proxy MimeMultipartFormData -> Binary -> ByteString
mimeRender Proxy MimeMultipartFormData
_ = Binary -> ByteString
unBinary
_readBinaryBase64 :: (MonadFail m) => Text -> m Binary
_readBinaryBase64 :: forall (m :: * -> *). MonadFail m => Text -> m Binary
_readBinaryBase64 = (String -> m Binary)
-> (ByteString -> m Binary) -> Either String ByteString -> m Binary
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
P.either String -> m Binary
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
P.fail (Binary -> m Binary
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Binary -> m Binary)
-> (ByteString -> Binary) -> ByteString -> m Binary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Binary
Binary) (Either String ByteString -> m Binary)
-> (Text -> Either String ByteString) -> Text -> m Binary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String ByteString
BL64.decode (ByteString -> Either String ByteString)
-> (Text -> ByteString) -> Text -> Either String ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL.fromStrict (ByteString -> ByteString)
-> (Text -> ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8
{-# INLINE _readBinaryBase64 #-}
_showBinaryBase64 :: Binary -> Text
_showBinaryBase64 :: Binary -> Text
_showBinaryBase64 = ByteString -> Text
T.decodeUtf8 (ByteString -> Text) -> (Binary -> ByteString) -> Binary -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL.toStrict (ByteString -> ByteString)
-> (Binary -> ByteString) -> Binary -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BL64.encode (ByteString -> ByteString)
-> (Binary -> ByteString) -> Binary -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary -> ByteString
unBinary
{-# INLINE _showBinaryBase64 #-}
type Lens_' s a = Lens_ s s a a
type Lens_ s t a b = forall (f :: K.Type -> K.Type). (Functor f) => (a -> f b) -> s -> f t