{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Blockfrost.Client.Sorting
( SortOrder (..)
, asc
, desc
) where
import Data.Proxy (Proxy (..))
import Servant.API ((:>))
import Servant.Client.Core (Client, HasClient (..))
import Blockfrost.Util.Sorting
( SortOrder (..)
, Sorting
, SortingExpanded
, asc
, desc
)
instance HasClient m subApi => HasClient m (Sorting :> subApi) where
type Client m (Sorting :> subApi) = SortOrder -> Client m subApi
clientWithRoute :: Proxy m
-> Proxy (Sorting :> subApi)
-> Request
-> Client m (Sorting :> subApi)
clientWithRoute Proxy m
pm Proxy (Sorting :> subApi)
_ Request
req SortOrder
sOrder =
Proxy m
-> Proxy (SortingExpanded subApi)
-> Request
-> Client m (SortingExpanded subApi)
forall (m :: * -> *) api.
HasClient m api =>
Proxy m -> Proxy api -> Request -> Client m api
clientWithRoute
Proxy m
pm
(forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @(SortingExpanded subApi))
Request
req
(SortOrder -> Maybe SortOrder
forall a. a -> Maybe a
Just SortOrder
sOrder)
hoistClientMonad :: forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy (Sorting :> subApi)
-> (forall x. mon x -> mon' x)
-> Client mon (Sorting :> subApi)
-> Client mon' (Sorting :> subApi)
hoistClientMonad Proxy m
pm Proxy (Sorting :> subApi)
_ forall x. mon x -> mon' x
hst Client mon (Sorting :> subApi)
subCli = Proxy m
-> Proxy subApi
-> (forall x. mon x -> mon' x)
-> Client mon subApi
-> Client mon' subApi
forall (m :: * -> *) api (mon :: * -> *) (mon' :: * -> *).
HasClient m api =>
Proxy m
-> Proxy api
-> (forall x. mon x -> mon' x)
-> Client mon api
-> Client mon' api
forall (mon :: * -> *) (mon' :: * -> *).
Proxy m
-> Proxy subApi
-> (forall x. mon x -> mon' x)
-> Client mon subApi
-> Client mon' subApi
hoistClientMonad Proxy m
pm (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @subApi) mon x -> mon' x
forall x. mon x -> mon' x
hst (Client mon subApi -> Client mon' subApi)
-> (SortOrder -> Client mon subApi)
-> SortOrder
-> Client mon' subApi
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Client mon (Sorting :> subApi)
SortOrder -> Client mon subApi
subCli