2015-04-20 19:52:29 +02:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
|
|
|
{-# LANGUAGE InstanceSigs #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
|
|
|
{-# LANGUAGE TypeFamilies #-}
|
|
|
|
{-# LANGUAGE TypeOperators #-}
|
|
|
|
#if !MIN_VERSION_base(4,8,0)
|
2015-03-26 14:34:38 +01:00
|
|
|
{-# LANGUAGE OverlappingInstances #-}
|
2015-04-20 19:52:29 +02:00
|
|
|
#endif
|
2014-11-27 18:28:01 +01:00
|
|
|
-- | This module provides 'client' which can automatically generate
|
|
|
|
-- querying functions for each endpoint just from the type representing your
|
|
|
|
-- API.
|
|
|
|
module Servant.Client
|
|
|
|
( client
|
|
|
|
, HasClient(..)
|
2015-04-19 18:31:23 +02:00
|
|
|
, Client
|
2015-03-05 02:46:35 +01:00
|
|
|
, ServantError(..)
|
2014-11-27 18:28:01 +01:00
|
|
|
, module Servant.Common.BaseUrl
|
|
|
|
) where
|
|
|
|
|
2015-04-20 19:52:29 +02:00
|
|
|
import Control.Monad
|
|
|
|
import Control.Monad.Trans.Either
|
|
|
|
import Data.ByteString.Lazy (ByteString)
|
|
|
|
import Data.List
|
|
|
|
import Data.Proxy
|
|
|
|
import Data.String.Conversions
|
|
|
|
import Data.Text (unpack)
|
|
|
|
import GHC.TypeLits
|
|
|
|
import Network.HTTP.Client (Response)
|
|
|
|
import Network.HTTP.Media
|
|
|
|
import qualified Network.HTTP.Types as H
|
|
|
|
import Servant.API
|
|
|
|
import Servant.API.ContentTypes
|
|
|
|
import Servant.Common.BaseUrl
|
|
|
|
import Servant.Common.Req
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- * Accessing APIs as a Client
|
|
|
|
|
|
|
|
-- | 'client' allows you to produce operations to query an API from a client.
|
|
|
|
--
|
|
|
|
-- > type MyApi = "books" :> Get [Book] -- GET /books
|
|
|
|
-- > :<|> "books" :> ReqBody Book :> Post Book -- POST /books
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
|
|
|
-- > getAllBooks :: BaseUrl -> EitherT String IO [Book]
|
|
|
|
-- > postNewBook :: Book -> BaseUrl -> EitherT String IO Book
|
|
|
|
-- > (getAllBooks :<|> postNewBook) = client myApi
|
2015-03-09 21:50:30 +01:00
|
|
|
client :: HasClient (Canonicalize layout) => Proxy layout -> Client layout
|
|
|
|
client p = clientWithRoute (canonicalize p) defReq
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- | This class lets us define how each API combinator
|
2014-12-01 13:41:12 +01:00
|
|
|
-- influences the creation of an HTTP request. It's mostly
|
|
|
|
-- an internal class, you can just use 'client'.
|
2014-11-27 18:28:01 +01:00
|
|
|
class HasClient layout where
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' layout :: *
|
|
|
|
clientWithRoute :: Proxy layout -> Req -> Client' layout
|
|
|
|
|
|
|
|
type Client layout = Client' (Canonicalize layout)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- | A client querying function for @a ':<|>' b@ will actually hand you
|
|
|
|
-- one function for querying @a@ and another one for querying @b@,
|
|
|
|
-- stitching them together with ':<|>', which really is just like a pair.
|
|
|
|
--
|
|
|
|
-- > type MyApi = "books" :> Get [Book] -- GET /books
|
|
|
|
-- > :<|> "books" :> ReqBody Book :> Post Book -- POST /books
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
|
|
|
-- > getAllBooks :: BaseUrl -> EitherT String IO [Book]
|
|
|
|
-- > postNewBook :: Book -> BaseUrl -> EitherT String IO Book
|
|
|
|
-- > (getAllBooks :<|> postNewBook) = client myApi
|
|
|
|
instance (HasClient a, HasClient b) => HasClient (a :<|> b) where
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (a :<|> b) = Client' a :<|> Client' b
|
2014-11-27 18:28:01 +01:00
|
|
|
clientWithRoute Proxy req =
|
|
|
|
clientWithRoute (Proxy :: Proxy a) req :<|>
|
|
|
|
clientWithRoute (Proxy :: Proxy b) req
|
|
|
|
|
|
|
|
-- | If you use a 'Capture' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
|
|
|
-- an additional argument of the type specified by your 'Capture'.
|
|
|
|
-- That function will take care of inserting a textual representation
|
|
|
|
-- of this value at the right place in the request path.
|
|
|
|
--
|
|
|
|
-- You can control how values for this type are turned into
|
|
|
|
-- text by specifying a 'ToText' instance for your type.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
|
|
|
-- > type MyApi = "books" :> Capture "isbn" Text :> Get Book
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
|
|
|
-- > getBook :: Text -> BaseUrl -> EitherT String IO Book
|
|
|
|
-- > getBook = client myApi
|
|
|
|
-- > -- then you can just use "getBook" to query that endpoint
|
|
|
|
instance (KnownSymbol capture, ToText a, HasClient sublayout)
|
|
|
|
=> HasClient (Capture capture a :> sublayout) where
|
|
|
|
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (Capture capture a :> sublayout) =
|
|
|
|
a -> Client' sublayout
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
clientWithRoute Proxy req val =
|
|
|
|
clientWithRoute (Proxy :: Proxy sublayout) $
|
|
|
|
appendToPath p req
|
|
|
|
|
|
|
|
where p = unpack (toText val)
|
|
|
|
|
|
|
|
-- | If you have a 'Delete' endpoint in your API, the client
|
|
|
|
-- side querying function that is created when calling 'client'
|
|
|
|
-- will just require an argument that specifies the scheme, host
|
|
|
|
-- and port to send the request to.
|
|
|
|
instance HasClient Delete where
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' Delete = BaseUrl -> EitherT ServantError IO ()
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
clientWithRoute Proxy req host =
|
2015-03-25 16:34:58 +01:00
|
|
|
void $ performRequest H.methodDelete req (`elem` [200, 202, 204]) host
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- | If you have a 'Get' endpoint in your API, the client
|
|
|
|
-- side querying function that is created when calling 'client'
|
|
|
|
-- will just require an argument that specifies the scheme, host
|
|
|
|
-- and port to send the request to.
|
2015-04-20 19:52:29 +02:00
|
|
|
instance
|
|
|
|
#if MIN_VERSION_base(4,8,0)
|
|
|
|
{-# OVERLAPPABLE #-}
|
|
|
|
#endif
|
|
|
|
(MimeUnrender ct result) => HasClient (Get (ct ': cts) result) where
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (Get (ct ': cts) result) = BaseUrl -> EitherT ServantError IO result
|
2014-11-27 18:28:01 +01:00
|
|
|
clientWithRoute Proxy req host =
|
2015-03-25 16:34:58 +01:00
|
|
|
performRequestCT (Proxy :: Proxy ct) H.methodGet req [200, 203] host
|
2014-12-08 12:52:30 +01:00
|
|
|
|
2015-03-26 14:34:38 +01:00
|
|
|
-- | If you have a 'Get xs ()' endpoint, the client expects a 204 No Content
|
|
|
|
-- HTTP header.
|
2015-04-20 19:52:29 +02:00
|
|
|
instance
|
|
|
|
#if MIN_VERSION_base(4,8,0)
|
|
|
|
{-# OVERLAPPING #-}
|
|
|
|
#endif
|
|
|
|
HasClient (Get (ct ': cts) ()) where
|
2015-04-19 18:31:23 +02:00
|
|
|
type Client' (Get (ct ': cts) ()) = BaseUrl -> EitherT ServantError IO ()
|
2015-03-26 14:34:38 +01:00
|
|
|
clientWithRoute Proxy req host =
|
|
|
|
performRequestNoBody H.methodGet req [204] host
|
|
|
|
|
2014-12-08 12:52:30 +01:00
|
|
|
-- | If you use a 'Header' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
|
|
|
-- an additional argument of the type specified by your 'Header',
|
|
|
|
-- wrapped in Maybe.
|
|
|
|
--
|
|
|
|
-- That function will take care of encoding this argument as Text
|
|
|
|
-- in the request headers.
|
|
|
|
--
|
|
|
|
-- All you need is for your type to have a 'ToText' instance.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
|
|
|
-- > newtype Referer = Referer Text
|
|
|
|
-- > deriving (Eq, Show, FromText, ToText)
|
|
|
|
-- >
|
|
|
|
-- > -- GET /view-my-referer
|
|
|
|
-- > type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get Referer
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
|
|
|
-- > viewReferer :: Maybe Referer -> BaseUrl -> EitherT String IO Book
|
|
|
|
-- > viewReferer = client myApi
|
|
|
|
-- > -- then you can just use "viewRefer" to query that endpoint
|
|
|
|
-- > -- specifying Nothing or Just "http://haskell.org/" as arguments
|
|
|
|
instance (KnownSymbol sym, ToText a, HasClient sublayout)
|
|
|
|
=> HasClient (Header sym a :> sublayout) where
|
|
|
|
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (Header sym a :> sublayout) =
|
|
|
|
Maybe a -> Client' sublayout
|
2014-12-08 12:52:30 +01:00
|
|
|
|
|
|
|
clientWithRoute Proxy req mval =
|
|
|
|
clientWithRoute (Proxy :: Proxy sublayout) $
|
2015-04-19 18:31:23 +02:00
|
|
|
maybe req (\value -> Servant.Common.Req.addHeader hname value req) mval
|
2014-12-08 12:52:30 +01:00
|
|
|
|
|
|
|
where hname = symbolVal (Proxy :: Proxy sym)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- | If you have a 'Post' endpoint in your API, the client
|
|
|
|
-- side querying function that is created when calling 'client'
|
|
|
|
-- will just require an argument that specifies the scheme, host
|
|
|
|
-- and port to send the request to.
|
2015-04-20 19:52:29 +02:00
|
|
|
instance
|
|
|
|
#if MIN_VERSION_base(4,8,0)
|
|
|
|
{-# OVERLAPPABLE #-}
|
|
|
|
#endif
|
|
|
|
(MimeUnrender ct a) => HasClient (Post (ct ': cts) a) where
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (Post (ct ': cts) a) = BaseUrl -> EitherT ServantError IO a
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
clientWithRoute Proxy req uri =
|
2015-03-09 07:04:31 +01:00
|
|
|
performRequestCT (Proxy :: Proxy ct) H.methodPost req [200,201] uri
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2015-03-26 14:34:38 +01:00
|
|
|
-- | If you have a 'Post xs ()' endpoint, the client expects a 204 No Content
|
|
|
|
-- HTTP header.
|
2015-04-20 19:52:29 +02:00
|
|
|
instance
|
|
|
|
#if MIN_VERSION_base(4,8,0)
|
|
|
|
{-# OVERLAPPING #-}
|
|
|
|
#endif
|
|
|
|
HasClient (Post (ct ': cts) ()) where
|
2015-04-19 18:31:23 +02:00
|
|
|
type Client' (Post (ct ': cts) ()) = BaseUrl -> EitherT ServantError IO ()
|
2015-03-26 14:34:38 +01:00
|
|
|
clientWithRoute Proxy req host =
|
|
|
|
void $ performRequestNoBody H.methodPost req [204] host
|
|
|
|
|
2014-11-27 18:28:01 +01:00
|
|
|
-- | If you have a 'Put' endpoint in your API, the client
|
|
|
|
-- side querying function that is created when calling 'client'
|
|
|
|
-- will just require an argument that specifies the scheme, host
|
|
|
|
-- and port to send the request to.
|
2015-04-20 19:52:29 +02:00
|
|
|
instance
|
|
|
|
#if MIN_VERSION_base(4,8,0)
|
|
|
|
{-# OVERLAPPABLE #-}
|
|
|
|
#endif
|
|
|
|
(MimeUnrender ct a) => HasClient (Put (ct ': cts) a) where
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (Put (ct ': cts) a) = BaseUrl -> EitherT ServantError IO a
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
clientWithRoute Proxy req host =
|
2015-03-09 07:04:31 +01:00
|
|
|
performRequestCT (Proxy :: Proxy ct) H.methodPut req [200,201] host
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2015-03-26 14:34:38 +01:00
|
|
|
-- | If you have a 'Put xs ()' endpoint, the client expects a 204 No Content
|
|
|
|
-- HTTP header.
|
2015-04-20 19:52:29 +02:00
|
|
|
instance
|
|
|
|
#if MIN_VERSION_base(4,8,0)
|
|
|
|
{-# OVERLAPPING #-}
|
|
|
|
#endif
|
|
|
|
HasClient (Put (ct ': cts) ()) where
|
2015-04-19 18:31:23 +02:00
|
|
|
type Client' (Put (ct ': cts) ()) = BaseUrl -> EitherT ServantError IO ()
|
2015-03-26 14:34:38 +01:00
|
|
|
clientWithRoute Proxy req host =
|
|
|
|
void $ performRequestNoBody H.methodPut req [204] host
|
|
|
|
|
|
|
|
-- | If you have a 'Patch' endpoint in your API, the client
|
|
|
|
-- side querying function that is created when calling 'client'
|
|
|
|
-- will just require an argument that specifies the scheme, host
|
|
|
|
-- and port to send the request to.
|
2015-04-20 19:52:29 +02:00
|
|
|
instance
|
|
|
|
#if MIN_VERSION_base(4,8,0)
|
|
|
|
{-# OVERLAPPABLE #-}
|
|
|
|
#endif
|
|
|
|
(MimeUnrender ct a) => HasClient (Patch (ct ': cts) a) where
|
2015-04-19 18:31:23 +02:00
|
|
|
type Client' (Patch (ct ': cts) a) = BaseUrl -> EitherT ServantError IO a
|
2015-03-26 14:34:38 +01:00
|
|
|
|
|
|
|
clientWithRoute Proxy req host =
|
|
|
|
performRequestCT (Proxy :: Proxy ct) H.methodPatch req [200,201] host
|
|
|
|
|
|
|
|
-- | If you have a 'Patch xs ()' endpoint, the client expects a 204 No Content
|
|
|
|
-- HTTP header.
|
2015-04-20 19:52:29 +02:00
|
|
|
instance
|
|
|
|
#if MIN_VERSION_base(4,8,0)
|
|
|
|
{-# OVERLAPPING #-}
|
|
|
|
#endif
|
|
|
|
HasClient (Patch (ct ': cts) ()) where
|
2015-04-19 18:31:23 +02:00
|
|
|
type Client' (Patch (ct ': cts) ()) = BaseUrl -> EitherT ServantError IO ()
|
2015-03-26 14:34:38 +01:00
|
|
|
clientWithRoute Proxy req host =
|
|
|
|
void $ performRequestNoBody H.methodPatch req [204] host
|
|
|
|
|
2014-11-27 18:28:01 +01:00
|
|
|
-- | If you use a 'QueryParam' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
|
|
|
-- an additional argument of the type specified by your 'QueryParam',
|
|
|
|
-- enclosed in Maybe.
|
|
|
|
--
|
|
|
|
-- If you give Nothing, nothing will be added to the query string.
|
|
|
|
--
|
|
|
|
-- If you give a non-'Nothing' value, this function will take care
|
|
|
|
-- of inserting a textual representation of this value in the query string.
|
|
|
|
--
|
|
|
|
-- You can control how values for your type are turned into
|
|
|
|
-- text by specifying a 'ToText' instance for your type.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
|
|
|
-- > type MyApi = "books" :> QueryParam "author" Text :> Get [Book]
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
|
|
|
-- > getBooksBy :: Maybe Text -> BaseUrl -> EitherT String IO [Book]
|
|
|
|
-- > getBooksBy = client myApi
|
|
|
|
-- > -- then you can just use "getBooksBy" to query that endpoint.
|
|
|
|
-- > -- 'getBooksBy Nothing' for all books
|
|
|
|
-- > -- 'getBooksBy (Just "Isaac Asimov")' to get all books by Isaac Asimov
|
|
|
|
instance (KnownSymbol sym, ToText a, HasClient sublayout)
|
|
|
|
=> HasClient (QueryParam sym a :> sublayout) where
|
|
|
|
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (QueryParam sym a :> sublayout) =
|
|
|
|
Maybe a -> Client' sublayout
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- if mparam = Nothing, we don't add it to the query string
|
|
|
|
clientWithRoute Proxy req mparam =
|
|
|
|
clientWithRoute (Proxy :: Proxy sublayout) $
|
2015-01-01 15:14:07 +01:00
|
|
|
maybe req (flip (appendToQueryString pname) req . Just) mparamText
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
where pname = cs pname'
|
|
|
|
pname' = symbolVal (Proxy :: Proxy sym)
|
|
|
|
mparamText = fmap toText mparam
|
|
|
|
|
|
|
|
-- | If you use a 'QueryParams' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
2015-03-26 14:34:38 +01:00
|
|
|
-- an additional argument, a list of values of the type specified
|
2014-11-27 18:28:01 +01:00
|
|
|
-- by your 'QueryParams'.
|
|
|
|
--
|
|
|
|
-- If you give an empty list, nothing will be added to the query string.
|
|
|
|
--
|
|
|
|
-- Otherwise, this function will take care
|
|
|
|
-- of inserting a textual representation of your values in the query string,
|
|
|
|
-- under the same query string parameter name.
|
|
|
|
--
|
|
|
|
-- You can control how values for your type are turned into
|
|
|
|
-- text by specifying a 'ToText' instance for your type.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
|
|
|
-- > type MyApi = "books" :> QueryParams "authors" Text :> Get [Book]
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
|
|
|
-- > getBooksBy :: [Text] -> BaseUrl -> EitherT String IO [Book]
|
|
|
|
-- > getBooksBy = client myApi
|
|
|
|
-- > -- then you can just use "getBooksBy" to query that endpoint.
|
|
|
|
-- > -- 'getBooksBy []' for all books
|
|
|
|
-- > -- 'getBooksBy ["Isaac Asimov", "Robert A. Heinlein"]'
|
|
|
|
-- > -- to get all books by Asimov and Heinlein
|
|
|
|
instance (KnownSymbol sym, ToText a, HasClient sublayout)
|
|
|
|
=> HasClient (QueryParams sym a :> sublayout) where
|
|
|
|
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (QueryParams sym a :> sublayout) =
|
|
|
|
[a] -> Client' sublayout
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
clientWithRoute Proxy req paramlist =
|
|
|
|
clientWithRoute (Proxy :: Proxy sublayout) $
|
2015-01-01 15:14:07 +01:00
|
|
|
foldl' (\ req' -> maybe req' (flip (appendToQueryString pname) req' . Just)) req paramlist'
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
where pname = cs pname'
|
|
|
|
pname' = symbolVal (Proxy :: Proxy sym)
|
|
|
|
paramlist' = map (Just . toText) paramlist
|
|
|
|
|
|
|
|
-- | If you use a 'QueryFlag' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
|
|
|
-- an additional 'Bool' argument.
|
|
|
|
--
|
|
|
|
-- If you give 'False', nothing will be added to the query string.
|
|
|
|
--
|
|
|
|
-- Otherwise, this function will insert a value-less query string
|
|
|
|
-- parameter under the name associated to your 'QueryFlag'.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
|
|
|
-- > type MyApi = "books" :> QueryFlag "published" :> Get [Book]
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
|
|
|
-- > getBooks :: Bool -> BaseUrl -> EitherT String IO [Book]
|
|
|
|
-- > getBooks = client myApi
|
|
|
|
-- > -- then you can just use "getBooks" to query that endpoint.
|
|
|
|
-- > -- 'getBooksBy False' for all books
|
|
|
|
-- > -- 'getBooksBy True' to only get _already published_ books
|
|
|
|
instance (KnownSymbol sym, HasClient sublayout)
|
|
|
|
=> HasClient (QueryFlag sym :> sublayout) where
|
|
|
|
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (QueryFlag sym :> sublayout) =
|
|
|
|
Bool -> Client' sublayout
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
clientWithRoute Proxy req flag =
|
|
|
|
clientWithRoute (Proxy :: Proxy sublayout) $
|
|
|
|
if flag
|
|
|
|
then appendToQueryString paramname Nothing req
|
|
|
|
else req
|
|
|
|
|
|
|
|
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
|
|
|
|
|
2015-01-01 23:43:29 +01:00
|
|
|
-- | If you use a 'MatrixParam' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
|
|
|
-- an additional argument of the type specified by your 'MatrixParam',
|
|
|
|
-- enclosed in Maybe.
|
|
|
|
--
|
|
|
|
-- If you give Nothing, nothing will be added to the query string.
|
|
|
|
--
|
|
|
|
-- If you give a non-'Nothing' value, this function will take care
|
|
|
|
-- of inserting a textual representation of this value in the query string.
|
|
|
|
--
|
|
|
|
-- You can control how values for your type are turned into
|
|
|
|
-- text by specifying a 'ToText' instance for your type.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
|
|
|
-- > type MyApi = "books" :> MatrixParam "author" Text :> Get [Book]
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
|
|
|
-- > getBooksBy :: Maybe Text -> BaseUrl -> EitherT String IO [Book]
|
|
|
|
-- > getBooksBy = client myApi
|
|
|
|
-- > -- then you can just use "getBooksBy" to query that endpoint.
|
|
|
|
-- > -- 'getBooksBy Nothing' for all books
|
|
|
|
-- > -- 'getBooksBy (Just "Isaac Asimov")' to get all books by Isaac Asimov
|
|
|
|
instance (KnownSymbol sym, ToText a, HasClient sublayout)
|
|
|
|
=> HasClient (MatrixParam sym a :> sublayout) where
|
|
|
|
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (MatrixParam sym a :> sublayout) =
|
|
|
|
Maybe a -> Client' sublayout
|
2015-01-01 23:43:29 +01:00
|
|
|
|
|
|
|
-- if mparam = Nothing, we don't add it to the query string
|
|
|
|
clientWithRoute Proxy req mparam =
|
|
|
|
clientWithRoute (Proxy :: Proxy sublayout) $
|
|
|
|
maybe req (flip (appendToMatrixParams pname . Just) req) mparamText
|
|
|
|
|
|
|
|
where pname = symbolVal (Proxy :: Proxy sym)
|
|
|
|
mparamText = fmap (cs . toText) mparam
|
|
|
|
|
|
|
|
-- | If you use a 'MatrixParams' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take an
|
|
|
|
-- additional argument, a list of values of the type specified by your
|
|
|
|
-- 'MatrixParams'.
|
|
|
|
--
|
|
|
|
-- If you give an empty list, nothing will be added to the query string.
|
|
|
|
--
|
|
|
|
-- Otherwise, this function will take care of inserting a textual
|
|
|
|
-- representation of your values in the path segment string, under the
|
|
|
|
-- same matrix string parameter name.
|
|
|
|
--
|
|
|
|
-- You can control how values for your type are turned into text by
|
|
|
|
-- specifying a 'ToText' instance for your type.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
|
|
|
-- > type MyApi = "books" :> MatrixParams "authors" Text :> Get [Book]
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
|
|
|
-- > getBooksBy :: [Text] -> BaseUrl -> EitherT String IO [Book]
|
|
|
|
-- > getBooksBy = client myApi
|
|
|
|
-- > -- then you can just use "getBooksBy" to query that endpoint.
|
|
|
|
-- > -- 'getBooksBy []' for all books
|
|
|
|
-- > -- 'getBooksBy ["Isaac Asimov", "Robert A. Heinlein"]'
|
|
|
|
-- > -- to get all books by Asimov and Heinlein
|
|
|
|
instance (KnownSymbol sym, ToText a, HasClient sublayout)
|
|
|
|
=> HasClient (MatrixParams sym a :> sublayout) where
|
|
|
|
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (MatrixParams sym a :> sublayout) =
|
|
|
|
[a] -> Client' sublayout
|
2015-01-01 23:43:29 +01:00
|
|
|
|
|
|
|
clientWithRoute Proxy req paramlist =
|
|
|
|
clientWithRoute (Proxy :: Proxy sublayout) $
|
|
|
|
foldl' (\ req' value -> maybe req' (flip (appendToMatrixParams pname) req' . Just . cs) value) req paramlist'
|
|
|
|
|
|
|
|
where pname = cs pname'
|
|
|
|
pname' = symbolVal (Proxy :: Proxy sym)
|
|
|
|
paramlist' = map (Just . toText) paramlist
|
|
|
|
|
|
|
|
-- | If you use a 'MatrixFlag' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take an
|
|
|
|
-- additional 'Bool' argument.
|
|
|
|
--
|
|
|
|
-- If you give 'False', nothing will be added to the path segment.
|
|
|
|
--
|
|
|
|
-- Otherwise, this function will insert a value-less matrix parameter
|
|
|
|
-- under the name associated to your 'MatrixFlag'.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
|
|
|
-- > type MyApi = "books" :> MatrixFlag "published" :> Get [Book]
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
|
|
|
-- > getBooks :: Bool -> BaseUrl -> EitherT String IO [Book]
|
|
|
|
-- > getBooks = client myApi
|
|
|
|
-- > -- then you can just use "getBooks" to query that endpoint.
|
|
|
|
-- > -- 'getBooksBy False' for all books
|
|
|
|
-- > -- 'getBooksBy True' to only get _already published_ books
|
|
|
|
instance (KnownSymbol sym, HasClient sublayout)
|
|
|
|
=> HasClient (MatrixFlag sym :> sublayout) where
|
|
|
|
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (MatrixFlag sym :> sublayout) =
|
|
|
|
Bool -> Client' sublayout
|
2015-01-01 23:43:29 +01:00
|
|
|
|
|
|
|
clientWithRoute Proxy req flag =
|
|
|
|
clientWithRoute (Proxy :: Proxy sublayout) $
|
|
|
|
if flag
|
|
|
|
then appendToMatrixParams paramname Nothing req
|
|
|
|
else req
|
|
|
|
|
|
|
|
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
|
|
|
|
|
2014-11-27 18:28:01 +01:00
|
|
|
-- | Pick a 'Method' and specify where the server you want to query is. You get
|
2015-03-16 01:12:11 +01:00
|
|
|
-- back the full `Response`.
|
2014-11-27 18:28:01 +01:00
|
|
|
instance HasClient Raw where
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' Raw = H.Method -> BaseUrl -> EitherT ServantError IO (Int, ByteString, MediaType, Response ByteString)
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2015-03-09 21:50:30 +01:00
|
|
|
clientWithRoute :: Proxy Raw -> Req -> Client' Raw
|
2015-03-16 01:12:11 +01:00
|
|
|
clientWithRoute Proxy req httpMethod host = do
|
2014-11-27 18:28:01 +01:00
|
|
|
performRequest httpMethod req (const True) host
|
|
|
|
|
|
|
|
-- | If you use a 'ReqBody' in one of your endpoints in your API,
|
|
|
|
-- the corresponding querying function will automatically take
|
|
|
|
-- an additional argument of the type specified by your 'ReqBody'.
|
|
|
|
-- That function will take care of encoding this argument as JSON and
|
|
|
|
-- of using it as the request body.
|
|
|
|
--
|
|
|
|
-- All you need is for your type to have a 'ToJSON' instance.
|
|
|
|
--
|
|
|
|
-- Example:
|
|
|
|
--
|
|
|
|
-- > type MyApi = "books" :> ReqBody Book :> Post Book
|
|
|
|
-- >
|
|
|
|
-- > myApi :: Proxy MyApi
|
|
|
|
-- > myApi = Proxy
|
|
|
|
-- >
|
|
|
|
-- > addBook :: Book -> BaseUrl -> EitherT String IO Book
|
|
|
|
-- > addBook = client myApi
|
|
|
|
-- > -- then you can just use "addBook" to query that endpoint
|
2015-02-24 23:30:31 +01:00
|
|
|
instance (MimeRender ct a, HasClient sublayout)
|
2015-02-17 07:17:10 +01:00
|
|
|
=> HasClient (ReqBody (ct ': cts) a :> sublayout) where
|
2014-11-27 18:28:01 +01:00
|
|
|
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (ReqBody (ct ': cts) a :> sublayout) =
|
|
|
|
a -> Client' sublayout
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
clientWithRoute Proxy req body =
|
2015-02-24 23:30:31 +01:00
|
|
|
clientWithRoute (Proxy :: Proxy sublayout) $ do
|
|
|
|
let ctProxy = Proxy :: Proxy ct
|
2015-04-19 18:31:23 +02:00
|
|
|
setRQBody (mimeRender ctProxy body) (contentType ctProxy) req
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
-- | Make the querying function append @path@ to the request path.
|
|
|
|
instance (KnownSymbol path, HasClient sublayout) => HasClient (path :> sublayout) where
|
2015-03-09 21:50:30 +01:00
|
|
|
type Client' (path :> sublayout) = Client' sublayout
|
2014-11-27 18:28:01 +01:00
|
|
|
|
|
|
|
clientWithRoute Proxy req =
|
|
|
|
clientWithRoute (Proxy :: Proxy sublayout) $
|
|
|
|
appendToPath p req
|
|
|
|
|
|
|
|
where p = symbolVal (Proxy :: Proxy path)
|
|
|
|
|