{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Servant.Client.Core.HasClient (
clientIn,
HasClient (..),
EmptyClient (..),
AsClientT,
(//),
(/:),
foldMapUnion,
matchUnion,
) where
import Prelude ()
import Prelude.Compat
import Control.Arrow
(left, (+++))
import Control.Monad
(unless)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL
import Data.Either
(partitionEithers)
import Data.Constraint (Dict(..))
import Data.Foldable
(toList)
import Data.List
(foldl')
import Data.Sequence
(fromList)
import qualified Data.Text as T
import Network.HTTP.Media
(MediaType, matches, parseAccept)
import qualified Network.HTTP.Media as Media
import qualified Data.Sequence as Seq
import Data.SOP.BasicFunctors
(I (I), (:.:) (Comp))
import Data.SOP.Constraint
(All)
import Data.SOP.NP
(NP (..), cpure_NP)
import Data.SOP.NS
(NS (S))
import Data.String
(fromString)
import Data.Text
(Text, pack)
import Data.Proxy
(Proxy (Proxy))
import GHC.TypeLits
(KnownNat, KnownSymbol, TypeError, symbolVal)
import Network.HTTP.Types
(Status)
import qualified Network.HTTP.Types as H
import Servant.API
((:<|>) ((:<|>)), (:>), AuthProtect, BasicAuth, BasicAuthData,
BuildHeadersTo (..), Capture', CaptureAll, Description,
EmptyAPI, Fragment, FramingRender (..), FramingUnrender (..),
FromSourceIO (..), Header', Headers (..), HttpVersion,
IsSecure, MimeRender (mimeRender),
MimeUnrender (mimeUnrender), NoContent (NoContent),
NoContentVerb, QueryFlag, QueryParam', QueryParams, Raw, RawM,
ReflectMethod (..), RemoteHost, ReqBody', SBoolI, Stream,
StreamBody', Summary, ToHttpApiData, ToSourceIO (..), Vault,
Verb, WithNamedContext, WithResource, WithStatus (..), contentType, getHeadersHList,
getResponse, toEncodedUrlPiece, toUrlPiece, NamedRoutes)
import Servant.API.Generic
(GenericMode(..), ToServant, ToServantApi
, GenericServant, toServant, fromServant)
import Servant.API.ContentTypes
(contentTypes, AllMime (allMime), AllMimeUnrender (allMimeUnrender))
import Servant.API.Status
(statusFromNat)
import Servant.API.TypeLevel (FragmentUnique, AtLeastOneFragment)
import Servant.API.Modifiers
(FoldRequired, RequiredArgument, foldRequiredArgument)
import Servant.API.TypeErrors
import Servant.API.UVerb
(HasStatus, HasStatuses (Statuses, statuses), UVerb, Union, Unique, inject, statusOf, foldMapUnion, matchUnion)
import Servant.Client.Core.Auth
import Servant.Client.Core.BasicAuth
import Servant.Client.Core.ClientError
import Servant.Client.Core.Request
import Servant.Client.Core.Response
import Servant.Client.Core.RunClient
clientIn :: HasClient m api => Proxy api -> Proxy m -> Client m api
clientIn :: forall (m :: * -> *) api.
HasClient m api =>
Proxy api -> Proxy m -> Client m api
clientIn Proxy api
p Proxy m
pm = forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm Proxy api
p Request
defaultRequest
class RunClient m => HasClient m api where
type Client (m :: * -> *) (api :: *) :: *
clientWithRoute :: Proxy m -> Proxy api -> Request -> Client m api
hoistClientMonad
:: Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
instance (HasClient m a, HasClient m b) => HasClient m (a :<|> b) where
type Client m (a :<|> b) = Client m a :<|> Client m b
clientWithRoute :: Proxy m -> Proxy (a :<|> b) -> Request -> Client m (a :<|> b)
clientWithRoute Proxy m
pm Proxy (a :<|> b)
Proxy Request
req =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy a) Request
req forall a b. a -> b -> a :<|> b
:<|>
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy b) Request
req
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (a :<|> b)
-> (forall x. mon x -> mon' x)
-> Client mon (a :<|> b)
-> Client mon' (a :<|> b)
hoistClientMonad Proxy m
pm Proxy (a :<|> b)
_ forall x. mon x -> mon' x
f (Client mon a
ca :<|> Client mon b
cb) =
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy a) forall x. mon x -> mon' x
f Client mon a
ca forall a b. a -> b -> a :<|> b
:<|>
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy b) forall x. mon x -> mon' x
f Client mon b
cb
data EmptyClient = EmptyClient deriving (EmptyClient -> EmptyClient -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmptyClient -> EmptyClient -> Bool
$c/= :: EmptyClient -> EmptyClient -> Bool
== :: EmptyClient -> EmptyClient -> Bool
$c== :: EmptyClient -> EmptyClient -> Bool
Eq, Int -> EmptyClient -> ShowS
[EmptyClient] -> ShowS
EmptyClient -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EmptyClient] -> ShowS
$cshowList :: [EmptyClient] -> ShowS
show :: EmptyClient -> String
$cshow :: EmptyClient -> String
showsPrec :: Int -> EmptyClient -> ShowS
$cshowsPrec :: Int -> EmptyClient -> ShowS
Show, EmptyClient
forall a. a -> a -> Bounded a
maxBound :: EmptyClient
$cmaxBound :: EmptyClient
minBound :: EmptyClient
$cminBound :: EmptyClient
Bounded, Int -> EmptyClient
EmptyClient -> Int
EmptyClient -> [EmptyClient]
EmptyClient -> EmptyClient
EmptyClient -> EmptyClient -> [EmptyClient]
EmptyClient -> EmptyClient -> EmptyClient -> [EmptyClient]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: EmptyClient -> EmptyClient -> EmptyClient -> [EmptyClient]
$cenumFromThenTo :: EmptyClient -> EmptyClient -> EmptyClient -> [EmptyClient]
enumFromTo :: EmptyClient -> EmptyClient -> [EmptyClient]
$cenumFromTo :: EmptyClient -> EmptyClient -> [EmptyClient]
enumFromThen :: EmptyClient -> EmptyClient -> [EmptyClient]
$cenumFromThen :: EmptyClient -> EmptyClient -> [EmptyClient]
enumFrom :: EmptyClient -> [EmptyClient]
$cenumFrom :: EmptyClient -> [EmptyClient]
fromEnum :: EmptyClient -> Int
$cfromEnum :: EmptyClient -> Int
toEnum :: Int -> EmptyClient
$ctoEnum :: Int -> EmptyClient
pred :: EmptyClient -> EmptyClient
$cpred :: EmptyClient -> EmptyClient
succ :: EmptyClient -> EmptyClient
$csucc :: EmptyClient -> EmptyClient
Enum)
instance RunClient m => HasClient m EmptyAPI where
type Client m EmptyAPI = EmptyClient
clientWithRoute :: Proxy m -> Proxy EmptyAPI -> Request -> Client m EmptyAPI
clientWithRoute Proxy m
_pm Proxy EmptyAPI
Proxy Request
_ = EmptyClient
EmptyClient
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy EmptyAPI
-> (forall x. mon x -> mon' x)
-> Client mon EmptyAPI
-> Client mon' EmptyAPI
hoistClientMonad Proxy m
_ Proxy EmptyAPI
_ forall x. mon x -> mon' x
_ EmptyClient
Client mon EmptyAPI
EmptyClient = EmptyClient
EmptyClient
instance (KnownSymbol capture, ToHttpApiData a, HasClient m api)
=> HasClient m (Capture' mods capture a :> api) where
type Client m (Capture' mods capture a :> api) =
a -> Client m api
clientWithRoute :: Proxy m
-> Proxy (Capture' mods capture a :> api)
-> Request
-> Client m (Capture' mods capture a :> api)
clientWithRoute Proxy m
pm Proxy (Capture' mods capture a :> api)
Proxy Request
req a
val =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
(Builder -> Request -> Request
appendToPath Builder
p Request
req)
where p :: Builder
p = forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece a
val
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Capture' mods capture a :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (Capture' mods capture a :> api)
-> Client mon' (Capture' mods capture a :> api)
hoistClientMonad Proxy m
pm Proxy (Capture' mods capture a :> api)
_ forall x. mon x -> mon' x
f Client mon (Capture' mods capture a :> api)
cl = \a
a ->
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f (Client mon (Capture' mods capture a :> api)
cl a
a)
instance (KnownSymbol capture, ToHttpApiData a, HasClient m sublayout)
=> HasClient m (CaptureAll capture a :> sublayout) where
type Client m (CaptureAll capture a :> sublayout) =
[a] -> Client m sublayout
clientWithRoute :: Proxy m
-> Proxy (CaptureAll capture a :> sublayout)
-> Request
-> Client m (CaptureAll capture a :> sublayout)
clientWithRoute Proxy m
pm Proxy (CaptureAll capture a :> sublayout)
Proxy Request
req [a]
vals =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy sublayout)
(forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (forall a b c. (a -> b -> c) -> b -> a -> c
flip Builder -> Request -> Request
appendToPath) Request
req [Builder]
ps)
where ps :: [Builder]
ps = forall a b. (a -> b) -> [a] -> [b]
map forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece [a]
vals
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (CaptureAll capture a :> sublayout)
-> (forall x. mon x -> mon' x)
-> Client mon (CaptureAll capture a :> sublayout)
-> Client mon' (CaptureAll capture a :> sublayout)
hoistClientMonad Proxy m
pm Proxy (CaptureAll capture a :> sublayout)
_ forall x. mon x -> mon' x
f Client mon (CaptureAll capture a :> sublayout)
cl = \[a]
as ->
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy sublayout) forall x. mon x -> mon' x
f (Client mon (CaptureAll capture a :> sublayout)
cl [a]
as)
instance {-# OVERLAPPABLE #-}
( RunClient m, MimeUnrender ct a, ReflectMethod method, cts' ~ (ct ': cts)
, KnownNat status
) => HasClient m (Verb method status cts' a) where
type Client m (Verb method status cts' a) = m a
clientWithRoute :: Proxy m
-> Proxy (Verb method status cts' a)
-> Request
-> Client m (Verb method status cts' a)
clientWithRoute Proxy m
_pm Proxy (Verb method status cts' a)
Proxy Request
req = do
Response
response <- forall (m :: * -> *).
RunClient m =>
Maybe [Status] -> Request -> m Response
runRequestAcceptStatus (forall a. a -> Maybe a
Just [Status
status]) Request
req
{ requestAccept :: Seq MediaType
requestAccept = forall a. [a] -> Seq a
fromList forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty MediaType
accept
, requestMethod :: Method
requestMethod = Method
method
}
Response
response forall {k} (ct :: k) a (m :: * -> *).
(MimeUnrender ct a, RunClient m) =>
Response -> Proxy ct -> m a
`decodedAs` (forall {k} (t :: k). Proxy t
Proxy :: Proxy ct)
where
accept :: NonEmpty MediaType
accept = forall {k} (ctype :: k).
Accept ctype =>
Proxy ctype -> NonEmpty MediaType
contentTypes (forall {k} (t :: k). Proxy t
Proxy :: Proxy ct)
method :: Method
method = forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
status :: Status
status = forall (a :: Nat) (proxy :: Nat -> *).
KnownNat a =>
proxy a -> Status
statusFromNat (forall {k} (t :: k). Proxy t
Proxy :: Proxy status)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Verb method status cts' a)
-> (forall x. mon x -> mon' x)
-> Client mon (Verb method status cts' a)
-> Client mon' (Verb method status cts' a)
hoistClientMonad Proxy m
_ Proxy (Verb method status cts' a)
_ forall x. mon x -> mon' x
f Client mon (Verb method status cts' a)
ma = forall x. mon x -> mon' x
f Client mon (Verb method status cts' a)
ma
instance {-# OVERLAPPING #-}
( RunClient m, ReflectMethod method, KnownNat status
) => HasClient m (Verb method status cts NoContent) where
type Client m (Verb method status cts NoContent)
= m NoContent
clientWithRoute :: Proxy m
-> Proxy (Verb method status cts NoContent)
-> Request
-> Client m (Verb method status cts NoContent)
clientWithRoute Proxy m
_pm Proxy (Verb method status cts NoContent)
Proxy Request
req = do
Response
_response <- forall (m :: * -> *).
RunClient m =>
Maybe [Status] -> Request -> m Response
runRequestAcceptStatus (forall a. a -> Maybe a
Just [Status
status]) Request
req { requestMethod :: Method
requestMethod = Method
method }
forall (m :: * -> *) a. Monad m => a -> m a
return NoContent
NoContent
where method :: Method
method = forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
status :: Status
status = forall (a :: Nat) (proxy :: Nat -> *).
KnownNat a =>
proxy a -> Status
statusFromNat (forall {k} (t :: k). Proxy t
Proxy :: Proxy status)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Verb method status cts NoContent)
-> (forall x. mon x -> mon' x)
-> Client mon (Verb method status cts NoContent)
-> Client mon' (Verb method status cts NoContent)
hoistClientMonad Proxy m
_ Proxy (Verb method status cts NoContent)
_ forall x. mon x -> mon' x
f Client mon (Verb method status cts NoContent)
ma = forall x. mon x -> mon' x
f Client mon (Verb method status cts NoContent)
ma
instance (RunClient m, ReflectMethod method) =>
HasClient m (NoContentVerb method) where
type Client m (NoContentVerb method)
= m NoContent
clientWithRoute :: Proxy m
-> Proxy (NoContentVerb method)
-> Request
-> Client m (NoContentVerb method)
clientWithRoute Proxy m
_pm Proxy (NoContentVerb method)
Proxy Request
req = do
Response
_response <- forall (m :: * -> *). RunClient m => Request -> m Response
runRequest Request
req { requestMethod :: Method
requestMethod = Method
method }
forall (m :: * -> *) a. Monad m => a -> m a
return NoContent
NoContent
where method :: Method
method = forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (NoContentVerb method)
-> (forall x. mon x -> mon' x)
-> Client mon (NoContentVerb method)
-> Client mon' (NoContentVerb method)
hoistClientMonad Proxy m
_ Proxy (NoContentVerb method)
_ forall x. mon x -> mon' x
f Client mon (NoContentVerb method)
ma = forall x. mon x -> mon' x
f Client mon (NoContentVerb method)
ma
instance {-# OVERLAPPING #-}
( RunClient m, MimeUnrender ct a, BuildHeadersTo ls, KnownNat status
, ReflectMethod method, cts' ~ (ct ': cts)
) => HasClient m (Verb method status cts' (Headers ls a)) where
type Client m (Verb method status cts' (Headers ls a))
= m (Headers ls a)
clientWithRoute :: Proxy m
-> Proxy (Verb method status cts' (Headers ls a))
-> Request
-> Client m (Verb method status cts' (Headers ls a))
clientWithRoute Proxy m
_pm Proxy (Verb method status cts' (Headers ls a))
Proxy Request
req = do
Response
response <- forall (m :: * -> *).
RunClient m =>
Maybe [Status] -> Request -> m Response
runRequestAcceptStatus (forall a. a -> Maybe a
Just [Status
status]) Request
req
{ requestMethod :: Method
requestMethod = Method
method
, requestAccept :: Seq MediaType
requestAccept = forall a. [a] -> Seq a
fromList forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty MediaType
accept
}
a
val <- Response
response forall {k} (ct :: k) a (m :: * -> *).
(MimeUnrender ct a, RunClient m) =>
Response -> Proxy ct -> m a
`decodedAs` (forall {k} (t :: k). Proxy t
Proxy :: Proxy ct)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Headers { getResponse :: a
getResponse = a
val
, getHeadersHList :: HList ls
getHeadersHList = forall (hs :: [*]). BuildHeadersTo hs => [Header] -> HList hs
buildHeadersTo forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall a. ResponseF a -> Seq Header
responseHeaders Response
response
}
where
method :: Method
method = forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
accept :: NonEmpty MediaType
accept = forall {k} (ctype :: k).
Accept ctype =>
Proxy ctype -> NonEmpty MediaType
contentTypes (forall {k} (t :: k). Proxy t
Proxy :: Proxy ct)
status :: Status
status = forall (a :: Nat) (proxy :: Nat -> *).
KnownNat a =>
proxy a -> Status
statusFromNat (forall {k} (t :: k). Proxy t
Proxy :: Proxy status)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Verb method status cts' (Headers ls a))
-> (forall x. mon x -> mon' x)
-> Client mon (Verb method status cts' (Headers ls a))
-> Client mon' (Verb method status cts' (Headers ls a))
hoistClientMonad Proxy m
_ Proxy (Verb method status cts' (Headers ls a))
_ forall x. mon x -> mon' x
f Client mon (Verb method status cts' (Headers ls a))
ma = forall x. mon x -> mon' x
f Client mon (Verb method status cts' (Headers ls a))
ma
instance {-# OVERLAPPING #-}
( RunClient m, BuildHeadersTo ls, ReflectMethod method, KnownNat status
) => HasClient m (Verb method status cts (Headers ls NoContent)) where
type Client m (Verb method status cts (Headers ls NoContent))
= m (Headers ls NoContent)
clientWithRoute :: Proxy m
-> Proxy (Verb method status cts (Headers ls NoContent))
-> Request
-> Client m (Verb method status cts (Headers ls NoContent))
clientWithRoute Proxy m
_pm Proxy (Verb method status cts (Headers ls NoContent))
Proxy Request
req = do
Response
response <- forall (m :: * -> *).
RunClient m =>
Maybe [Status] -> Request -> m Response
runRequestAcceptStatus (forall a. a -> Maybe a
Just [Status
status]) Request
req { requestMethod :: Method
requestMethod = Method
method }
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Headers { getResponse :: NoContent
getResponse = NoContent
NoContent
, getHeadersHList :: HList ls
getHeadersHList = forall (hs :: [*]). BuildHeadersTo hs => [Header] -> HList hs
buildHeadersTo forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall a. ResponseF a -> Seq Header
responseHeaders Response
response
}
where
method :: Method
method = forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
status :: Status
status = forall (a :: Nat) (proxy :: Nat -> *).
KnownNat a =>
proxy a -> Status
statusFromNat (forall {k} (t :: k). Proxy t
Proxy :: Proxy status)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Verb method status cts (Headers ls NoContent))
-> (forall x. mon x -> mon' x)
-> Client mon (Verb method status cts (Headers ls NoContent))
-> Client mon' (Verb method status cts (Headers ls NoContent))
hoistClientMonad Proxy m
_ Proxy (Verb method status cts (Headers ls NoContent))
_ forall x. mon x -> mon' x
f Client mon (Verb method status cts (Headers ls NoContent))
ma = forall x. mon x -> mon' x
f Client mon (Verb method status cts (Headers ls NoContent))
ma
data ClientParseError = ClientParseError MediaType String | ClientStatusMismatch | ClientNoMatchingStatus
deriving (ClientParseError -> ClientParseError -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClientParseError -> ClientParseError -> Bool
$c/= :: ClientParseError -> ClientParseError -> Bool
== :: ClientParseError -> ClientParseError -> Bool
$c== :: ClientParseError -> ClientParseError -> Bool
Eq, Int -> ClientParseError -> ShowS
[ClientParseError] -> ShowS
ClientParseError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClientParseError] -> ShowS
$cshowList :: [ClientParseError] -> ShowS
show :: ClientParseError -> String
$cshow :: ClientParseError -> String
showsPrec :: Int -> ClientParseError -> ShowS
$cshowsPrec :: Int -> ClientParseError -> ShowS
Show)
class UnrenderResponse (cts :: [*]) (a :: *) where
unrenderResponse :: Seq.Seq H.Header -> BL.ByteString -> Proxy cts
-> [Either (MediaType, String) a]
instance {-# OVERLAPPABLE #-} AllMimeUnrender cts a => UnrenderResponse cts a where
unrenderResponse :: Seq Header
-> ByteString -> Proxy cts -> [Either (MediaType, String) a]
unrenderResponse Seq Header
_ ByteString
body = forall a b. (a -> b) -> [a] -> [b]
map (MediaType, ByteString -> Either String a)
-> Either (MediaType, String) a
parse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (list :: [*]) a.
AllMimeUnrender list a =>
Proxy list -> [(MediaType, ByteString -> Either String a)]
allMimeUnrender
where parse :: (MediaType, ByteString -> Either String a)
-> Either (MediaType, String) a
parse (MediaType
mediaType, ByteString -> Either String a
parser) = forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either b d) (Either c d)
left ((,) MediaType
mediaType) (ByteString -> Either String a
parser ByteString
body)
instance {-# OVERLAPPING #-} forall cts a h . (UnrenderResponse cts a, BuildHeadersTo h)
=> UnrenderResponse cts (Headers h a) where
unrenderResponse :: Seq Header
-> ByteString
-> Proxy cts
-> [Either (MediaType, String) (Headers h a)]
unrenderResponse Seq Header
hs ByteString
body = (forall a b. (a -> b) -> [a] -> [b]
map forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) a -> Headers h a
setHeaders forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (cts :: [*]) a.
UnrenderResponse cts a =>
Seq Header
-> ByteString -> Proxy cts -> [Either (MediaType, String) a]
unrenderResponse Seq Header
hs ByteString
body
where
setHeaders :: a -> Headers h a
setHeaders :: a -> Headers h a
setHeaders a
x = forall (ls :: [*]) a. a -> HList ls -> Headers ls a
Headers a
x (forall (hs :: [*]). BuildHeadersTo hs => [Header] -> HList hs
buildHeadersTo (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Seq Header
hs))
instance {-# OVERLAPPING #-} UnrenderResponse cts a
=> UnrenderResponse cts (WithStatus n a) where
unrenderResponse :: Seq Header
-> ByteString
-> Proxy cts
-> [Either (MediaType, String) (WithStatus n a)]
unrenderResponse Seq Header
hs ByteString
body = (forall a b. (a -> b) -> [a] -> [b]
map forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) forall (k :: Nat) a. a -> WithStatus k a
WithStatus forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (cts :: [*]) a.
UnrenderResponse cts a =>
Seq Header
-> ByteString -> Proxy cts -> [Either (MediaType, String) a]
unrenderResponse Seq Header
hs ByteString
body
instance {-# OVERLAPPING #-}
( RunClient m,
contentTypes ~ (contentType ': otherContentTypes),
as ~ (a ': as'),
AllMime contentTypes,
ReflectMethod method,
All (UnrenderResponse contentTypes) as,
All HasStatus as, HasStatuses as',
Unique (Statuses as)
) =>
HasClient m (UVerb method contentTypes as)
where
type Client m (UVerb method contentTypes as) = m (Union as)
clientWithRoute :: Proxy m
-> Proxy (UVerb method contentTypes as)
-> Request
-> Client m (UVerb method contentTypes as)
clientWithRoute Proxy m
_ Proxy (UVerb method contentTypes as)
_ Request
request = do
let accept :: Seq MediaType
accept = forall a. [a] -> Seq a
Seq.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (list :: [*]). AllMime list => Proxy list -> [MediaType]
allMime forall a b. (a -> b) -> a -> b
$ forall {k} (t :: k). Proxy t
Proxy @contentTypes
method :: Method
method = forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod forall a b. (a -> b) -> a -> b
$ forall {k} (t :: k). Proxy t
Proxy @method
acceptStatus :: [Status]
acceptStatus = forall (as :: [*]). HasStatuses as => Proxy as -> [Status]
statuses (forall {k} (t :: k). Proxy t
Proxy @as)
Response
response <- forall (m :: * -> *).
RunClient m =>
Maybe [Status] -> Request -> m Response
runRequestAcceptStatus (forall a. a -> Maybe a
Just [Status]
acceptStatus) Request
request {requestMethod :: Method
requestMethod = Method
method, requestAccept :: Seq MediaType
requestAccept = Seq MediaType
accept}
MediaType
responseContentType <- forall (m :: * -> *). RunClient m => Response -> m MediaType
checkContentTypeHeader Response
response
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Accept a => a -> a -> Bool
matches MediaType
responseContentType) Seq MediaType
accept) forall a b. (a -> b) -> a -> b
$ do
forall (m :: * -> *) a. RunClient m => ClientError -> m a
throwClientError forall a b. (a -> b) -> a -> b
$ MediaType -> Response -> ClientError
UnsupportedContentType MediaType
responseContentType Response
response
let status :: Status
status = forall a. ResponseF a -> Status
responseStatusCode Response
response
body :: ByteString
body = forall a. ResponseF a -> a
responseBody Response
response
headers :: Seq Header
headers = forall a. ResponseF a -> Seq Header
responseHeaders Response
response
res :: Either [ClientParseError] (Union (a : as'))
res = forall (xs :: [*]).
All HasStatus xs =>
Status
-> NP ([] :.: Either (MediaType, String)) xs
-> Either [ClientParseError] (Union xs)
tryParsers Status
status forall a b. (a -> b) -> a -> b
$ forall (cts :: [*]) (xs :: [*]).
All (UnrenderResponse cts) xs =>
Proxy cts
-> Seq Header
-> ByteString
-> NP ([] :.: Either (MediaType, String)) xs
mimeUnrenders (forall {k} (t :: k). Proxy t
Proxy @contentTypes) Seq Header
headers ByteString
body
case Either [ClientParseError] (Union (a : as'))
res of
Left [ClientParseError]
errors -> forall (m :: * -> *) a. RunClient m => ClientError -> m a
throwClientError forall a b. (a -> b) -> a -> b
$ Text -> Response -> ClientError
DecodeFailure (String -> Text
T.pack (forall a. Show a => a -> String
show [ClientParseError]
errors)) Response
response
Right Union (a : as')
x -> forall (m :: * -> *) a. Monad m => a -> m a
return Union (a : as')
x
where
tryParsers :: forall xs. All HasStatus xs => Status -> NP ([] :.: Either (MediaType, String)) xs -> Either [ClientParseError] (Union xs)
tryParsers :: forall (xs :: [*]).
All HasStatus xs =>
Status
-> NP ([] :.: Either (MediaType, String)) xs
-> Either [ClientParseError] (Union xs)
tryParsers Status
_ NP ([] :.: Either (MediaType, String)) xs
Nil = forall a b. a -> Either a b
Left [ClientParseError
ClientNoMatchingStatus]
tryParsers Status
status (Comp [Either (MediaType, String) x]
x :* NP ([] :.: Either (MediaType, String)) xs
xs)
| Status
status forall a. Eq a => a -> a -> Bool
== forall a (proxy :: * -> *). HasStatus a => proxy a -> Status
statusOf (forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp [Either (MediaType, String) x]
x) =
case forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either (MediaType, String) x]
x of
([(MediaType, String)]
err', []) -> (forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry MediaType -> String -> ClientParseError
ClientParseError) [(MediaType, String)]
err' forall a. [a] -> [a] -> [a]
++) forall (a :: * -> * -> *) b c b' c'.
ArrowChoice a =>
a b c -> a b' c' -> a (Either b b') (Either c c')
+++ forall {k} (a :: k -> *) (xs :: [k]) (x :: k).
NS a xs -> NS a (x : xs)
S forall a b. (a -> b) -> a -> b
$ forall (xs :: [*]).
All HasStatus xs =>
Status
-> NP ([] :.: Either (MediaType, String)) xs
-> Either [ClientParseError] (Union xs)
tryParsers Status
status NP ([] :.: Either (MediaType, String)) xs
xs
([(MediaType, String)]
_, (x
res : [x]
_)) -> forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (x :: k) (xs :: [k]) (f :: k -> *).
UElem x xs =>
f x -> NS f xs
inject forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> I a
I forall a b. (a -> b) -> a -> b
$ x
res
| Bool
otherwise =
(ClientParseError
ClientStatusMismatch forall a. a -> [a] -> [a]
:) forall (a :: * -> * -> *) b c b' c'.
ArrowChoice a =>
a b c -> a b' c' -> a (Either b b') (Either c c')
+++ forall {k} (a :: k -> *) (xs :: [k]) (x :: k).
NS a xs -> NS a (x : xs)
S forall a b. (a -> b) -> a -> b
$ forall (xs :: [*]).
All HasStatus xs =>
Status
-> NP ([] :.: Either (MediaType, String)) xs
-> Either [ClientParseError] (Union xs)
tryParsers Status
status NP ([] :.: Either (MediaType, String)) xs
xs
mimeUnrenders ::
forall cts xs.
All (UnrenderResponse cts) xs =>
Proxy cts ->
Seq.Seq H.Header ->
BL.ByteString ->
NP ([] :.: Either (MediaType, String)) xs
mimeUnrenders :: forall (cts :: [*]) (xs :: [*]).
All (UnrenderResponse cts) xs =>
Proxy cts
-> Seq Header
-> ByteString
-> NP ([] :.: Either (MediaType, String)) xs
mimeUnrenders Proxy cts
ctp Seq Header
headers ByteString
body = forall {k} (c :: k -> Constraint) (xs :: [k])
(proxy :: (k -> Constraint) -> *) (f :: k -> *).
All c xs =>
proxy c -> (forall (a :: k). c a => f a) -> NP f xs
cpure_NP
(forall {k} (t :: k). Proxy t
Proxy @(UnrenderResponse cts))
(forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (cts :: [*]) a.
UnrenderResponse cts a =>
Seq Header
-> ByteString -> Proxy cts -> [Either (MediaType, String) a]
unrenderResponse Seq Header
headers ByteString
body forall a b. (a -> b) -> a -> b
$ Proxy cts
ctp)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (UVerb method contentTypes as)
-> (forall x. mon x -> mon' x)
-> Client mon (UVerb method contentTypes as)
-> Client mon' (UVerb method contentTypes as)
hoistClientMonad Proxy m
_ Proxy (UVerb method contentTypes as)
_ forall x. mon x -> mon' x
nt Client mon (UVerb method contentTypes as)
s = forall x. mon x -> mon' x
nt Client mon (UVerb method contentTypes as)
s
instance {-# OVERLAPPABLE #-}
( RunStreamingClient m, MimeUnrender ct chunk, ReflectMethod method,
FramingUnrender framing, FromSourceIO chunk a
) => HasClient m (Stream method status framing ct a) where
type Client m (Stream method status framing ct a) = m a
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Stream method status framing ct a)
-> (forall x. mon x -> mon' x)
-> Client mon (Stream method status framing ct a)
-> Client mon' (Stream method status framing ct a)
hoistClientMonad Proxy m
_ Proxy (Stream method status framing ct a)
_ forall x. mon x -> mon' x
f Client mon (Stream method status framing ct a)
ma = forall x. mon x -> mon' x
f Client mon (Stream method status framing ct a)
ma
clientWithRoute :: Proxy m
-> Proxy (Stream method status framing ct a)
-> Request
-> Client m (Stream method status framing ct a)
clientWithRoute Proxy m
_pm Proxy (Stream method status framing ct a)
Proxy Request
req = forall (m :: * -> *) a.
RunStreamingClient m =>
Request -> (StreamingResponse -> IO a) -> m a
withStreamingRequest Request
req' forall a b. (a -> b) -> a -> b
$ \StreamingResponse
gres -> do
let mimeUnrender' :: ByteString -> Either String chunk
mimeUnrender' = forall {k} (ctype :: k) a.
MimeUnrender ctype a =>
Proxy ctype -> ByteString -> Either String a
mimeUnrender (forall {k} (t :: k). Proxy t
Proxy :: Proxy ct) :: BL.ByteString -> Either String chunk
framingUnrender' :: SourceT IO Method -> SourceT IO chunk
framingUnrender' = forall {k} (strategy :: k) (m :: * -> *) a.
(FramingUnrender strategy, Monad m) =>
Proxy strategy
-> (ByteString -> Either String a)
-> SourceT m Method
-> SourceT m a
framingUnrender (forall {k} (t :: k). Proxy t
Proxy :: Proxy framing) ByteString -> Either String chunk
mimeUnrender'
forall chunk a. FromSourceIO chunk a => SourceIO chunk -> IO a
fromSourceIO forall a b. (a -> b) -> a -> b
$ SourceT IO Method -> SourceT IO chunk
framingUnrender' forall a b. (a -> b) -> a -> b
$ forall a. ResponseF a -> a
responseBody StreamingResponse
gres
where
req' :: Request
req' = Request
req
{ requestAccept :: Seq MediaType
requestAccept = forall a. [a] -> Seq a
fromList [forall {k} (ctype :: k). Accept ctype => Proxy ctype -> MediaType
contentType (forall {k} (t :: k). Proxy t
Proxy :: Proxy ct)]
, requestMethod :: Method
requestMethod = forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
}
instance {-# OVERLAPPING #-}
( RunStreamingClient m, MimeUnrender ct chunk, ReflectMethod method,
FramingUnrender framing, FromSourceIO chunk a,
BuildHeadersTo hs
) => HasClient m (Stream method status framing ct (Headers hs a)) where
type Client m (Stream method status framing ct (Headers hs a)) = m (Headers hs a)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Stream method status framing ct (Headers hs a))
-> (forall x. mon x -> mon' x)
-> Client mon (Stream method status framing ct (Headers hs a))
-> Client mon' (Stream method status framing ct (Headers hs a))
hoistClientMonad Proxy m
_ Proxy (Stream method status framing ct (Headers hs a))
_ forall x. mon x -> mon' x
f Client mon (Stream method status framing ct (Headers hs a))
ma = forall x. mon x -> mon' x
f Client mon (Stream method status framing ct (Headers hs a))
ma
clientWithRoute :: Proxy m
-> Proxy (Stream method status framing ct (Headers hs a))
-> Request
-> Client m (Stream method status framing ct (Headers hs a))
clientWithRoute Proxy m
_pm Proxy (Stream method status framing ct (Headers hs a))
Proxy Request
req = forall (m :: * -> *) a.
RunStreamingClient m =>
Request -> (StreamingResponse -> IO a) -> m a
withStreamingRequest Request
req' forall a b. (a -> b) -> a -> b
$ \StreamingResponse
gres -> do
let mimeUnrender' :: ByteString -> Either String chunk
mimeUnrender' = forall {k} (ctype :: k) a.
MimeUnrender ctype a =>
Proxy ctype -> ByteString -> Either String a
mimeUnrender (forall {k} (t :: k). Proxy t
Proxy :: Proxy ct) :: BL.ByteString -> Either String chunk
framingUnrender' :: SourceT IO Method -> SourceT IO chunk
framingUnrender' = forall {k} (strategy :: k) (m :: * -> *) a.
(FramingUnrender strategy, Monad m) =>
Proxy strategy
-> (ByteString -> Either String a)
-> SourceT m Method
-> SourceT m a
framingUnrender (forall {k} (t :: k). Proxy t
Proxy :: Proxy framing) ByteString -> Either String chunk
mimeUnrender'
a
val <- forall chunk a. FromSourceIO chunk a => SourceIO chunk -> IO a
fromSourceIO forall a b. (a -> b) -> a -> b
$ SourceT IO Method -> SourceT IO chunk
framingUnrender' forall a b. (a -> b) -> a -> b
$ forall a. ResponseF a -> a
responseBody StreamingResponse
gres
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Headers
{ getResponse :: a
getResponse = a
val
, getHeadersHList :: HList hs
getHeadersHList = forall (hs :: [*]). BuildHeadersTo hs => [Header] -> HList hs
buildHeadersTo forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall a. ResponseF a -> Seq Header
responseHeaders StreamingResponse
gres
}
where
req' :: Request
req' = Request
req
{ requestAccept :: Seq MediaType
requestAccept = forall a. [a] -> Seq a
fromList [forall {k} (ctype :: k). Accept ctype => Proxy ctype -> MediaType
contentType (forall {k} (t :: k). Proxy t
Proxy :: Proxy ct)]
, requestMethod :: Method
requestMethod = forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
}
instance (KnownSymbol sym, ToHttpApiData a, HasClient m api, SBoolI (FoldRequired mods))
=> HasClient m (Header' mods sym a :> api) where
type Client m (Header' mods sym a :> api) =
RequiredArgument mods a -> Client m api
clientWithRoute :: Proxy m
-> Proxy (Header' mods sym a :> api)
-> Request
-> Client m (Header' mods sym a :> api)
clientWithRoute Proxy m
pm Proxy (Header' mods sym a :> api)
Proxy Request
req If (FoldRequired mods) a (Maybe a)
mval =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall a b. (a -> b) -> a -> b
$ forall (mods :: [*]) a r.
SBoolI (FoldRequired mods) =>
Proxy mods
-> (a -> r) -> (Maybe a -> r) -> RequiredArgument mods a -> r
foldRequiredArgument
(forall {k} (t :: k). Proxy t
Proxy :: Proxy mods) a -> Request
add (forall b a. b -> (a -> b) -> Maybe a -> b
maybe Request
req a -> Request
add) If (FoldRequired mods) a (Maybe a)
mval
where
hname :: HeaderName
hname = forall a. IsString a => String -> a
fromString forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy sym)
add :: a -> Request
add :: a -> Request
add a
value = forall a. ToHttpApiData a => HeaderName -> a -> Request -> Request
addHeader HeaderName
hname a
value Request
req
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Header' mods sym a :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (Header' mods sym a :> api)
-> Client mon' (Header' mods sym a :> api)
hoistClientMonad Proxy m
pm Proxy (Header' mods sym a :> api)
_ forall x. mon x -> mon' x
f Client mon (Header' mods sym a :> api)
cl = \If (FoldRequired mods) a (Maybe a)
arg ->
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f (Client mon (Header' mods sym a :> api)
cl If (FoldRequired mods) a (Maybe a)
arg)
instance HasClient m api
=> HasClient m (HttpVersion :> api) where
type Client m (HttpVersion :> api) =
Client m api
clientWithRoute :: Proxy m
-> Proxy (HttpVersion :> api)
-> Request
-> Client m (HttpVersion :> api)
clientWithRoute Proxy m
pm Proxy (HttpVersion :> api)
Proxy =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (HttpVersion :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (HttpVersion :> api)
-> Client mon' (HttpVersion :> api)
hoistClientMonad Proxy m
pm Proxy (HttpVersion :> api)
_ forall x. mon x -> mon' x
f Client mon (HttpVersion :> api)
cl = forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f Client mon (HttpVersion :> api)
cl
instance HasClient m api => HasClient m (Summary desc :> api) where
type Client m (Summary desc :> api) = Client m api
clientWithRoute :: Proxy m
-> Proxy (Summary desc :> api)
-> Request
-> Client m (Summary desc :> api)
clientWithRoute Proxy m
pm Proxy (Summary desc :> api)
_ = forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Summary desc :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (Summary desc :> api)
-> Client mon' (Summary desc :> api)
hoistClientMonad Proxy m
pm Proxy (Summary desc :> api)
_ forall x. mon x -> mon' x
f Client mon (Summary desc :> api)
cl = forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f Client mon (Summary desc :> api)
cl
instance HasClient m api => HasClient m (Description desc :> api) where
type Client m (Description desc :> api) = Client m api
clientWithRoute :: Proxy m
-> Proxy (Description desc :> api)
-> Request
-> Client m (Description desc :> api)
clientWithRoute Proxy m
pm Proxy (Description desc :> api)
_ = forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Description desc :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (Description desc :> api)
-> Client mon' (Description desc :> api)
hoistClientMonad Proxy m
pm Proxy (Description desc :> api)
_ forall x. mon x -> mon' x
f Client mon (Description desc :> api)
cl = forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f Client mon (Description desc :> api)
cl
instance (KnownSymbol sym, ToHttpApiData a, HasClient m api, SBoolI (FoldRequired mods))
=> HasClient m (QueryParam' mods sym a :> api) where
type Client m (QueryParam' mods sym a :> api) =
RequiredArgument mods a -> Client m api
clientWithRoute :: Proxy m
-> Proxy (QueryParam' mods sym a :> api)
-> Request
-> Client m (QueryParam' mods sym a :> api)
clientWithRoute Proxy m
pm Proxy (QueryParam' mods sym a :> api)
Proxy Request
req If (FoldRequired mods) a (Maybe a)
mparam =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall a b. (a -> b) -> a -> b
$ forall (mods :: [*]) a r.
SBoolI (FoldRequired mods) =>
Proxy mods
-> (a -> r) -> (Maybe a -> r) -> RequiredArgument mods a -> r
foldRequiredArgument
(forall {k} (t :: k). Proxy t
Proxy :: Proxy mods) a -> Request
add (forall b a. b -> (a -> b) -> Maybe a -> b
maybe Request
req a -> Request
add) If (FoldRequired mods) a (Maybe a)
mparam
where
add :: a -> Request
add :: a -> Request
add a
param = Text -> Maybe Method -> Request -> Request
appendToQueryString Text
pname (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. ToHttpApiData a => a -> Method
encodeQueryParamValue a
param) Request
req
pname :: Text
pname :: Text
pname = String -> Text
pack forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy sym)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (QueryParam' mods sym a :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (QueryParam' mods sym a :> api)
-> Client mon' (QueryParam' mods sym a :> api)
hoistClientMonad Proxy m
pm Proxy (QueryParam' mods sym a :> api)
_ forall x. mon x -> mon' x
f Client mon (QueryParam' mods sym a :> api)
cl = \If (FoldRequired mods) a (Maybe a)
arg ->
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f (Client mon (QueryParam' mods sym a :> api)
cl If (FoldRequired mods) a (Maybe a)
arg)
instance (KnownSymbol sym, ToHttpApiData a, HasClient m api)
=> HasClient m (QueryParams sym a :> api) where
type Client m (QueryParams sym a :> api) =
[a] -> Client m api
clientWithRoute :: Proxy m
-> Proxy (QueryParams sym a :> api)
-> Request
-> Client m (QueryParams sym a :> api)
clientWithRoute Proxy m
pm Proxy (QueryParams sym a :> api)
Proxy Request
req [a]
paramlist =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
(forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\ Request
req' -> forall b a. b -> (a -> b) -> Maybe a -> b
maybe Request
req' (forall a b c. (a -> b -> c) -> b -> a -> c
flip (Text -> Maybe Method -> Request -> Request
appendToQueryString Text
pname) Request
req' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just))
Request
req
[Maybe Method]
paramlist'
)
where pname :: Text
pname = String -> Text
pack forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy sym)
paramlist' :: [Maybe Method]
paramlist' = forall a b. (a -> b) -> [a] -> [b]
map (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToHttpApiData a => a -> Method
encodeQueryParamValue) [a]
paramlist
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (QueryParams sym a :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (QueryParams sym a :> api)
-> Client mon' (QueryParams sym a :> api)
hoistClientMonad Proxy m
pm Proxy (QueryParams sym a :> api)
_ forall x. mon x -> mon' x
f Client mon (QueryParams sym a :> api)
cl = \[a]
as ->
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f (Client mon (QueryParams sym a :> api)
cl [a]
as)
instance (KnownSymbol sym, HasClient m api)
=> HasClient m (QueryFlag sym :> api) where
type Client m (QueryFlag sym :> api) =
Bool -> Client m api
clientWithRoute :: Proxy m
-> Proxy (QueryFlag sym :> api)
-> Request
-> Client m (QueryFlag sym :> api)
clientWithRoute Proxy m
pm Proxy (QueryFlag sym :> api)
Proxy Request
req Bool
flag =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
(if Bool
flag
then Text -> Maybe Method -> Request -> Request
appendToQueryString Text
paramname forall a. Maybe a
Nothing Request
req
else Request
req
)
where paramname :: Text
paramname = String -> Text
pack forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy sym)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (QueryFlag sym :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (QueryFlag sym :> api)
-> Client mon' (QueryFlag sym :> api)
hoistClientMonad Proxy m
pm Proxy (QueryFlag sym :> api)
_ forall x. mon x -> mon' x
f Client mon (QueryFlag sym :> api)
cl = \Bool
b ->
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f (Client mon (QueryFlag sym :> api)
cl Bool
b)
instance RunClient m => HasClient m Raw where
type Client m Raw
= H.Method -> m Response
clientWithRoute :: Proxy m -> Proxy Raw -> Request -> Client m Raw
clientWithRoute :: Proxy m -> Proxy Raw -> Request -> Client m Raw
clientWithRoute Proxy m
_pm Proxy Raw
Proxy Request
req Method
httpMethod = do
forall (m :: * -> *). RunClient m => Request -> m Response
runRequest Request
req { requestMethod :: Method
requestMethod = Method
httpMethod }
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy Raw
-> (forall x. mon x -> mon' x)
-> Client mon Raw
-> Client mon' Raw
hoistClientMonad Proxy m
_ Proxy Raw
_ forall x. mon x -> mon' x
f Client mon Raw
cl = \Method
meth -> forall x. mon x -> mon' x
f (Client mon Raw
cl Method
meth)
instance RunClient m => HasClient m RawM where
type Client m RawM
= H.Method -> m Response
clientWithRoute :: Proxy m -> Proxy RawM -> Request -> Client m RawM
clientWithRoute :: Proxy m -> Proxy RawM -> Request -> Client m RawM
clientWithRoute Proxy m
_pm Proxy RawM
Proxy Request
req Method
httpMethod = do
forall (m :: * -> *). RunClient m => Request -> m Response
runRequest Request
req { requestMethod :: Method
requestMethod = Method
httpMethod }
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy RawM
-> (forall x. mon x -> mon' x)
-> Client mon RawM
-> Client mon' RawM
hoistClientMonad Proxy m
_ Proxy RawM
_ forall x. mon x -> mon' x
f Client mon RawM
cl = \Method
meth -> forall x. mon x -> mon' x
f (Client mon RawM
cl Method
meth)
instance (MimeRender ct a, HasClient m api)
=> HasClient m (ReqBody' mods (ct ': cts) a :> api) where
type Client m (ReqBody' mods (ct ': cts) a :> api) =
a -> Client m api
clientWithRoute :: Proxy m
-> Proxy (ReqBody' mods (ct : cts) a :> api)
-> Request
-> Client m (ReqBody' mods (ct : cts) a :> api)
clientWithRoute Proxy m
pm Proxy (ReqBody' mods (ct : cts) a :> api)
Proxy Request
req a
body =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
(let ctProxy :: Proxy ct
ctProxy = forall {k} (t :: k). Proxy t
Proxy :: Proxy ct
in ByteString -> MediaType -> Request -> Request
setRequestBodyLBS (forall {k} (ctype :: k) a.
MimeRender ctype a =>
Proxy ctype -> a -> ByteString
mimeRender Proxy ct
ctProxy a
body)
(forall {k} (ctype :: k). Accept ctype => Proxy ctype -> MediaType
contentType Proxy ct
ctProxy)
Request
req
)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (ReqBody' mods (ct : cts) a :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (ReqBody' mods (ct : cts) a :> api)
-> Client mon' (ReqBody' mods (ct : cts) a :> api)
hoistClientMonad Proxy m
pm Proxy (ReqBody' mods (ct : cts) a :> api)
_ forall x. mon x -> mon' x
f Client mon (ReqBody' mods (ct : cts) a :> api)
cl = \a
a ->
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f (Client mon (ReqBody' mods (ct : cts) a :> api)
cl a
a)
instance
( HasClient m api, MimeRender ctype chunk, FramingRender framing, ToSourceIO chunk a
) => HasClient m (StreamBody' mods framing ctype a :> api)
where
type Client m (StreamBody' mods framing ctype a :> api) = a -> Client m api
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (StreamBody' mods framing ctype a :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (StreamBody' mods framing ctype a :> api)
-> Client mon' (StreamBody' mods framing ctype a :> api)
hoistClientMonad Proxy m
pm Proxy (StreamBody' mods framing ctype a :> api)
_ forall x. mon x -> mon' x
f Client mon (StreamBody' mods framing ctype a :> api)
cl = \a
a ->
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f (Client mon (StreamBody' mods framing ctype a :> api)
cl a
a)
clientWithRoute :: Proxy m
-> Proxy (StreamBody' mods framing ctype a :> api)
-> Request
-> Client m (StreamBody' mods framing ctype a :> api)
clientWithRoute Proxy m
pm Proxy (StreamBody' mods framing ctype a :> api)
Proxy Request
req a
body
= forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
forall a b. (a -> b) -> a -> b
$ RequestBody -> MediaType -> Request -> Request
setRequestBody (SourceIO ByteString -> RequestBody
RequestBodySource SourceIO ByteString
sourceIO) (forall {k} (ctype :: k). Accept ctype => Proxy ctype -> MediaType
contentType Proxy ctype
ctypeP) Request
req
where
ctypeP :: Proxy ctype
ctypeP = forall {k} (t :: k). Proxy t
Proxy :: Proxy ctype
framingP :: Proxy framing
framingP = forall {k} (t :: k). Proxy t
Proxy :: Proxy framing
sourceIO :: SourceIO ByteString
sourceIO = forall {k} (strategy :: k) (m :: * -> *) a.
(FramingRender strategy, Monad m) =>
Proxy strategy
-> (a -> ByteString) -> SourceT m a -> SourceT m ByteString
framingRender
Proxy framing
framingP
(forall {k} (ctype :: k) a.
MimeRender ctype a =>
Proxy ctype -> a -> ByteString
mimeRender Proxy ctype
ctypeP :: chunk -> BL.ByteString)
(forall chunk a. ToSourceIO chunk a => a -> SourceIO chunk
toSourceIO a
body)
instance (KnownSymbol path, HasClient m api) => HasClient m (path :> api) where
type Client m (path :> api) = Client m api
clientWithRoute :: Proxy m -> Proxy (path :> api) -> Request -> Client m (path :> api)
clientWithRoute Proxy m
pm Proxy (path :> api)
Proxy Request
req =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
(Builder -> Request -> Request
appendToPath Builder
p Request
req)
where p :: Builder
p = forall a. ToHttpApiData a => a -> Builder
toEncodedUrlPiece forall a b. (a -> b) -> a -> b
$ String -> Text
pack forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy path)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (path :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (path :> api)
-> Client mon' (path :> api)
hoistClientMonad Proxy m
pm Proxy (path :> api)
_ forall x. mon x -> mon' x
f Client mon (path :> api)
cl = forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f Client mon (path :> api)
cl
instance HasClient m api => HasClient m (Vault :> api) where
type Client m (Vault :> api) = Client m api
clientWithRoute :: Proxy m
-> Proxy (Vault :> api) -> Request -> Client m (Vault :> api)
clientWithRoute Proxy m
pm Proxy (Vault :> api)
Proxy Request
req =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) Request
req
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Vault :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (Vault :> api)
-> Client mon' (Vault :> api)
hoistClientMonad Proxy m
pm Proxy (Vault :> api)
_ forall x. mon x -> mon' x
f Client mon (Vault :> api)
cl = forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f Client mon (Vault :> api)
cl
instance HasClient m api => HasClient m (RemoteHost :> api) where
type Client m (RemoteHost :> api) = Client m api
clientWithRoute :: Proxy m
-> Proxy (RemoteHost :> api)
-> Request
-> Client m (RemoteHost :> api)
clientWithRoute Proxy m
pm Proxy (RemoteHost :> api)
Proxy Request
req =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) Request
req
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (RemoteHost :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (RemoteHost :> api)
-> Client mon' (RemoteHost :> api)
hoistClientMonad Proxy m
pm Proxy (RemoteHost :> api)
_ forall x. mon x -> mon' x
f Client mon (RemoteHost :> api)
cl = forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f Client mon (RemoteHost :> api)
cl
instance HasClient m api => HasClient m (IsSecure :> api) where
type Client m (IsSecure :> api) = Client m api
clientWithRoute :: Proxy m
-> Proxy (IsSecure :> api) -> Request -> Client m (IsSecure :> api)
clientWithRoute Proxy m
pm Proxy (IsSecure :> api)
Proxy Request
req =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) Request
req
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (IsSecure :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (IsSecure :> api)
-> Client mon' (IsSecure :> api)
hoistClientMonad Proxy m
pm Proxy (IsSecure :> api)
_ forall x. mon x -> mon' x
f Client mon (IsSecure :> api)
cl = forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f Client mon (IsSecure :> api)
cl
instance HasClient m subapi =>
HasClient m (WithNamedContext name context subapi) where
type Client m (WithNamedContext name context subapi) = Client m subapi
clientWithRoute :: Proxy m
-> Proxy (WithNamedContext name context subapi)
-> Request
-> Client m (WithNamedContext name context subapi)
clientWithRoute Proxy m
pm Proxy (WithNamedContext name context subapi)
Proxy = forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy subapi)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (WithNamedContext name context subapi)
-> (forall x. mon x -> mon' x)
-> Client mon (WithNamedContext name context subapi)
-> Client mon' (WithNamedContext name context subapi)
hoistClientMonad Proxy m
pm Proxy (WithNamedContext name context subapi)
_ forall x. mon x -> mon' x
f Client mon (WithNamedContext name context subapi)
cl = forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy subapi) forall x. mon x -> mon' x
f Client mon (WithNamedContext name context subapi)
cl
instance HasClient m subapi =>
HasClient m (WithResource res :> subapi) where
type Client m (WithResource res :> subapi) = Client m subapi
clientWithRoute :: Proxy m
-> Proxy (WithResource res :> subapi)
-> Request
-> Client m (WithResource res :> subapi)
clientWithRoute Proxy m
pm Proxy (WithResource res :> subapi)
Proxy = forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy subapi)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (WithResource res :> subapi)
-> (forall x. mon x -> mon' x)
-> Client mon (WithResource res :> subapi)
-> Client mon' (WithResource res :> subapi)
hoistClientMonad Proxy m
pm Proxy (WithResource res :> subapi)
_ forall x. mon x -> mon' x
f Client mon (WithResource res :> subapi)
cl = forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy subapi) forall x. mon x -> mon' x
f Client mon (WithResource res :> subapi)
cl
instance ( HasClient m api
) => HasClient m (AuthProtect tag :> api) where
type Client m (AuthProtect tag :> api)
= AuthenticatedRequest (AuthProtect tag) -> Client m api
clientWithRoute :: Proxy m
-> Proxy (AuthProtect tag :> api)
-> Request
-> Client m (AuthProtect tag :> api)
clientWithRoute Proxy m
pm Proxy (AuthProtect tag :> api)
Proxy Request
req (AuthenticatedRequest (AuthClientData (AuthProtect tag)
val,AuthClientData (AuthProtect tag) -> Request -> Request
func)) =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (AuthClientData (AuthProtect tag) -> Request -> Request
func AuthClientData (AuthProtect tag)
val Request
req)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (AuthProtect tag :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (AuthProtect tag :> api)
-> Client mon' (AuthProtect tag :> api)
hoistClientMonad Proxy m
pm Proxy (AuthProtect tag :> api)
_ forall x. mon x -> mon' x
f Client mon (AuthProtect tag :> api)
cl = \AuthenticatedRequest (AuthProtect tag)
authreq ->
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f (Client mon (AuthProtect tag :> api)
cl AuthenticatedRequest (AuthProtect tag)
authreq)
instance (AtLeastOneFragment api, FragmentUnique (Fragment a :> api), HasClient m api
) => HasClient m (Fragment a :> api) where
type Client m (Fragment a :> api) = Client m api
clientWithRoute :: Proxy m
-> Proxy (Fragment a :> api)
-> Request
-> Client m (Fragment a :> api)
clientWithRoute Proxy m
pm Proxy (Fragment a :> api)
_ = forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Fragment a :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (Fragment a :> api)
-> Client mon' (Fragment a :> api)
hoistClientMonad Proxy m
pm Proxy (Fragment a :> api)
_ = forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
instance HasClient m api => HasClient m (BasicAuth realm usr :> api) where
type Client m (BasicAuth realm usr :> api) = BasicAuthData -> Client m api
clientWithRoute :: Proxy m
-> Proxy (BasicAuth realm usr :> api)
-> Request
-> Client m (BasicAuth realm usr :> api)
clientWithRoute Proxy m
pm Proxy (BasicAuth realm usr :> api)
Proxy Request
req BasicAuthData
val =
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (BasicAuthData -> Request -> Request
basicAuthReq BasicAuthData
val Request
req)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (BasicAuth realm usr :> api)
-> (forall x. mon x -> mon' x)
-> Client mon (BasicAuth realm usr :> api)
-> Client mon' (BasicAuth realm usr :> api)
hoistClientMonad Proxy m
pm Proxy (BasicAuth realm usr :> api)
_ forall x. mon x -> mon' x
f Client mon (BasicAuth realm usr :> api)
cl = \BasicAuthData
bauth ->
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) forall x. mon x -> mon' x
f (Client mon (BasicAuth realm usr :> api)
cl BasicAuthData
bauth)
data AsClientT (m :: * -> *)
instance GenericMode (AsClientT m) where
type AsClientT m :- api = Client m api
type GClientConstraints api m =
( GenericServant api (AsClientT m)
, Client m (ToServantApi api) ~ ToServant api (AsClientT m)
)
class GClient (api :: * -> *) m where
gClientProof :: Dict (GClientConstraints api m)
instance GClientConstraints api m => GClient api m where
gClientProof :: Dict (GClientConstraints api m)
gClientProof = forall (a :: Constraint). a => Dict a
Dict
instance
( forall n. GClient api n
, HasClient m (ToServantApi api)
, RunClient m
, ErrorIfNoGeneric api
)
=> HasClient m (NamedRoutes api) where
type Client m (NamedRoutes api) = api (AsClientT m)
clientWithRoute :: Proxy m -> Proxy (NamedRoutes api) -> Request -> Client m (NamedRoutes api)
clientWithRoute :: Proxy m
-> Proxy (NamedRoutes api) -> Request -> Client m (NamedRoutes api)
clientWithRoute Proxy m
pm Proxy (NamedRoutes api)
_ Request
request =
case forall (api :: * -> *) (m :: * -> *).
GClient api m =>
Dict (GClientConstraints api m)
gClientProof @api @m of
Dict (GClientConstraints api m)
Dict -> forall (routes :: * -> *) mode.
GenericServant routes mode =>
ToServant routes mode -> routes mode
fromServant forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute Proxy m
pm (forall {k} (t :: k). Proxy t
Proxy @(ToServantApi api)) Request
request
hoistClientMonad
:: forall ma mb.
Proxy m
-> Proxy (NamedRoutes api)
-> (forall x. ma x -> mb x)
-> Client ma (NamedRoutes api)
-> Client mb (NamedRoutes api)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (NamedRoutes api)
-> (forall x. mon x -> mon' x)
-> Client mon (NamedRoutes api)
-> Client mon' (NamedRoutes api)
hoistClientMonad Proxy m
_ Proxy (NamedRoutes api)
_ forall x. ma x -> mb x
nat Client ma (NamedRoutes api)
clientA =
case (forall (api :: * -> *) (m :: * -> *).
GClient api m =>
Dict (GClientConstraints api m)
gClientProof @api @ma, forall (api :: * -> *) (m :: * -> *).
GClient api m =>
Dict (GClientConstraints api m)
gClientProof @api @mb) of
(Dict
((GenericMode (AsClientT ma), Generic (api (AsClientT ma)),
GServantProduct (Rep (api (AsClientT ma)))),
Client ma (ToServantApi api)
~ GToServant (Rep (api (AsClientT ma))))
Dict, Dict
((GenericMode (AsClientT mb), Generic (api (AsClientT mb)),
GServantProduct (Rep (api (AsClientT mb)))),
Client mb (ToServantApi api)
~ GToServant (Rep (api (AsClientT mb))))
Dict) ->
forall (routes :: * -> *) mode.
GenericServant routes mode =>
ToServant routes mode -> routes mode
fromServant @api @(AsClientT mb) forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
hoistClientMonad @m @(ToServantApi api) @ma @mb forall {k} (t :: k). Proxy t
Proxy forall {k} (t :: k). Proxy t
Proxy forall x. ma x -> mb x
nat forall a b. (a -> b) -> a -> b
$
forall (routes :: * -> *) mode.
GenericServant routes mode =>
routes mode -> ToServant routes mode
toServant @api @(AsClientT ma) Client ma (NamedRoutes api)
clientA
infixl 1 //
infixl 2 /:
(//) :: a -> (a -> b) -> b
a
x // :: forall a b. a -> (a -> b) -> b
// a -> b
f = a -> b
f a
x
(/:) :: (a -> b -> c) -> b -> a -> c
/: :: forall a b c. (a -> b -> c) -> b -> a -> c
(/:) = forall a b c. (a -> b -> c) -> b -> a -> c
flip
checkContentTypeHeader :: RunClient m => Response -> m MediaType
Response
response =
case forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup HeaderName
"Content-Type" forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall a. ResponseF a -> Seq Header
responseHeaders Response
response of
Maybe Method
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Method
"application" Method -> Method -> MediaType
Media.// Method
"octet-stream"
Just Method
t -> case forall a. Accept a => Method -> Maybe a
parseAccept Method
t of
Maybe MediaType
Nothing -> forall (m :: * -> *) a. RunClient m => ClientError -> m a
throwClientError forall a b. (a -> b) -> a -> b
$ Response -> ClientError
InvalidContentTypeHeader Response
response
Just MediaType
t' -> forall (m :: * -> *) a. Monad m => a -> m a
return MediaType
t'
decodedAs :: forall ct a m. (MimeUnrender ct a, RunClient m)
=> Response -> Proxy ct -> m a
decodedAs :: forall {k} (ct :: k) a (m :: * -> *).
(MimeUnrender ct a, RunClient m) =>
Response -> Proxy ct -> m a
decodedAs Response
response Proxy ct
ct = do
MediaType
responseContentType <- forall (m :: * -> *). RunClient m => Response -> m MediaType
checkContentTypeHeader Response
response
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Accept a => a -> a -> Bool
matches MediaType
responseContentType) [MediaType]
accept) forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. RunClient m => ClientError -> m a
throwClientError forall a b. (a -> b) -> a -> b
$ MediaType -> Response -> ClientError
UnsupportedContentType MediaType
responseContentType Response
response
case forall {k} (ctype :: k) a.
MimeUnrender ctype a =>
Proxy ctype -> ByteString -> Either String a
mimeUnrender Proxy ct
ct forall a b. (a -> b) -> a -> b
$ forall a. ResponseF a -> a
responseBody Response
response of
Left String
err -> forall (m :: * -> *) a. RunClient m => ClientError -> m a
throwClientError forall a b. (a -> b) -> a -> b
$ Text -> Response -> ClientError
DecodeFailure (String -> Text
T.pack String
err) Response
response
Right a
val -> forall (m :: * -> *) a. Monad m => a -> m a
return a
val
where
accept :: [MediaType]
accept = forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall {k} (ctype :: k).
Accept ctype =>
Proxy ctype -> NonEmpty MediaType
contentTypes Proxy ct
ct
instance (RunClient m, TypeError (PartialApplication HasClient arr)) => HasClient m ((arr :: a -> b) :> sub)
where
type Client m (arr :> sub) = TypeError (PartialApplication HasClient arr)
clientWithRoute :: Proxy m -> Proxy (arr :> sub) -> Request -> Client m (arr :> sub)
clientWithRoute Proxy m
_ Proxy (arr :> sub)
_ Request
_ = forall a. HasCallStack => String -> a
error String
"unreachable"
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (arr :> sub)
-> (forall x. mon x -> mon' x)
-> Client mon (arr :> sub)
-> Client mon' (arr :> sub)
hoistClientMonad Proxy m
_ Proxy (arr :> sub)
_ forall x. mon x -> mon' x
_ Client mon (arr :> sub)
_ = forall a. HasCallStack => String -> a
error String
"unreachable"
instance {-# OVERLAPPABLE #-} (RunClient m, TypeError (NoInstanceForSub (HasClient m) ty)) => HasClient m (ty :> sub)
instance {-# OVERLAPPABLE #-} (RunClient m, TypeError (NoInstanceFor (HasClient m api))) => HasClient m api