Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class ClientLike client custom where
- mkClient :: client -> custom
- class GClientLikeP client xs where
- gMkClientP :: client -> NP I xs
- class GClientLikeL (xs :: [*]) (ys :: [*]) where
- gMkClientL :: NP I xs -> NP I ys
- type family ClientList (client :: *) (acc :: [*]) :: [*] where ...
- class GClientList client (acc :: [*]) where
- gClientList :: client -> NP I acc -> NP I (ClientList client acc)
- genericMkClientL :: (Generic custom, Code custom ~ '[xs], GClientList client '[], GClientLikeL (ClientList client '[]) xs) => client -> custom
- genericMkClientP :: (Generic custom, Code custom ~ '[xs], GClientLikeP client xs) => client -> custom
Documentation
class ClientLike client custom where Source #
This class allows us to match client structure with client functions
produced with client
without explicit pattern-matching.
The client structure needs a Generic
instance.
Example:
type API = "foo" :> Capture "x" Int :> Get '[JSON] Int :<|> "bar" :> QueryParam "a" Char :> QueryParam "b" String :> Post '[JSON] [Int] :<|> Capture "nested" Int :> NestedAPI type NestedAPI = Get '[JSON] String :<|> "baz" :> QueryParam "c" Char :> Post '[JSON] () data APIClient = APIClient { getFoo :: Int -> ClientM Int , postBar :: Maybe Char -> Maybe String -> ClientM [Int] , mkNestedClient :: Int -> NestedClient } deriving GHC.Generic instance Generics.SOP.Generic APIClient instance (Client API ~ client) => ClientLike client APIClient data NestedClient = NestedClient { getString :: ClientM String , postBaz :: Maybe Char -> ClientM () } deriving GHC.Generic instance Generics.SOP.Generic NestedClient instance (Client NestedAPI ~ client) => ClientLike client NestedClient mkAPIClient :: APIClient mkAPIClient = mkClient (client (Proxy :: Proxy API))
By default, left-nested alternatives are expanded:
type API1 = "foo" :> Capture "x" Int :> Get '[JSON] Int :<|> "bar" :> QueryParam "a" Char :> Post '[JSON] String type API2 = "baz" :> QueryParam "c" Char :> Post '[JSON] () type API = API1 :<|> API2 data APIClient = APIClient { getFoo :: Int -> ClientM Int , postBar :: Maybe Char -> ClientM String , postBaz :: Maybe Char -> ClientM () } deriving GHC.Generic instance Generics.SOP.Generic APIClient instance (Client API ~ client) => ClientLike client APIClient mkAPIClient :: APIClient mkAPIClient = mkClient (client (Proxy :: Proxy API))
If you want to define client for API1
as a separate data structure,
you can use genericMkClientP
:
data APIClient1 = APIClient1 { getFoo :: Int -> ClientM Int , postBar :: Maybe Char -> ClientM String } deriving GHC.Generic instance Generics.SOP.Generic APIClient1 instance (Client API1 ~ client) => ClientLike client APIClient1 data APIClient = APIClient { mkAPIClient1 :: APIClient1 , postBaz :: Maybe Char -> ClientM () } deriving GHC.Generic instance Generics.SOP.Generic APIClient instance (Client API ~ client) => ClientLike client APIClient where mkClient = genericMkClientP mkAPIClient :: APIClient mkAPIClient = mkClient (client (Proxy :: Proxy API))
Nothing
mkClient :: client -> custom Source #
mkClient :: (Generic custom, Code custom ~ '[xs], GClientList client '[], GClientLikeL (ClientList client '[]) xs) => client -> custom Source #
Instances
ClientLike client custom => ClientLike (a -> client) (a -> custom) Source # | |
Defined in Servant.Client.Core.Internal.Generic |
class GClientLikeP client xs where Source #
Match client structure with client functions, regarding left-nested API clients as separate data structures.
gMkClientP :: client -> NP I xs Source #
Instances
ClientLike a x => GClientLikeP a (x ': ([] :: [Type])) Source # | |
Defined in Servant.Client.Core.Internal.Generic gMkClientP :: a -> NP I (x ': []) Source # | |
(GClientLikeP b (y ': xs), ClientLike a x) => GClientLikeP (a :<|> b) (x ': (y ': xs)) Source # | |
Defined in Servant.Client.Core.Internal.Generic |
class GClientLikeL (xs :: [*]) (ys :: [*]) where Source #
Match client structure with client functions, expanding left-nested API clients in the same structure.
Instances
GClientLikeL ([] :: [Type]) ([] :: [Type]) Source # | |
Defined in Servant.Client.Core.Internal.Generic | |
(ClientLike x y, GClientLikeL xs ys) => GClientLikeL (x ': xs) (y ': ys) Source # | |
Defined in Servant.Client.Core.Internal.Generic |
type family ClientList (client :: *) (acc :: [*]) :: [*] where ... Source #
ClientList (a :<|> b) acc = ClientList a (ClientList b acc) | |
ClientList a acc = a ': acc |
class GClientList client (acc :: [*]) where Source #
gClientList :: client -> NP I acc -> NP I (ClientList client acc) Source #
Instances
ClientList client acc ~ (client ': acc) => GClientList client acc Source # | |
Defined in Servant.Client.Core.Internal.Generic gClientList :: client -> NP I acc -> NP I (ClientList client acc) Source # | |
(GClientList b acc, GClientList a (ClientList b acc)) => GClientList (a :<|> b) acc Source # | |
Defined in Servant.Client.Core.Internal.Generic gClientList :: (a :<|> b) -> NP I acc -> NP I (ClientList (a :<|> b) acc) Source # |
genericMkClientL :: (Generic custom, Code custom ~ '[xs], GClientList client '[], GClientLikeL (ClientList client '[]) xs) => client -> custom Source #
Generate client structure from client type, expanding left-nested API (done by default).
genericMkClientP :: (Generic custom, Code custom ~ '[xs], GClientLikeP client xs) => client -> custom Source #
Generate client structure from client type, regarding left-nested API clients as separate data structures.