Merge pull request #2 from dlarsson/master
Support for matrix parameters
This commit is contained in:
commit
83e46f41ef
5 changed files with 175 additions and 6 deletions
17
.gitignore
vendored
Normal file
17
.gitignore
vendored
Normal file
|
@ -0,0 +1,17 @@
|
||||||
|
dist
|
||||||
|
cabal-dev
|
||||||
|
*.o
|
||||||
|
*.hi
|
||||||
|
*.chi
|
||||||
|
*.chs.h
|
||||||
|
*.dyn_o
|
||||||
|
*.dyn_hi
|
||||||
|
.virtualenv
|
||||||
|
.hpc
|
||||||
|
.hsenv
|
||||||
|
.cabal-sandbox/
|
||||||
|
cabal.sandbox.config
|
||||||
|
cabal.config
|
||||||
|
*.prof
|
||||||
|
*.aux
|
||||||
|
*.hp
|
|
@ -1,5 +1,5 @@
|
||||||
name: servant-client
|
name: servant-client
|
||||||
version: 0.2.1
|
version: 0.2.2
|
||||||
synopsis: automatical derivation of querying functions for servant webservices
|
synopsis: automatical derivation of querying functions for servant webservices
|
||||||
description:
|
description:
|
||||||
This library lets you derive automatically Haskell functions that
|
This library lets you derive automatically Haskell functions that
|
||||||
|
@ -47,7 +47,7 @@ library
|
||||||
, http-types
|
, http-types
|
||||||
, network-uri >= 2.6
|
, network-uri >= 2.6
|
||||||
, safe
|
, safe
|
||||||
, servant >= 0.2.1
|
, servant >= 0.2.2
|
||||||
, string-conversions
|
, string-conversions
|
||||||
, text
|
, text
|
||||||
, transformers
|
, transformers
|
||||||
|
@ -71,7 +71,7 @@ test-suite spec
|
||||||
, hspec == 2.*
|
, hspec == 2.*
|
||||||
, http-types
|
, http-types
|
||||||
, network >= 2.6
|
, network >= 2.6
|
||||||
, QuickCheck
|
, QuickCheck >= 2.7
|
||||||
, servant >= 0.2.1
|
, servant >= 0.2.1
|
||||||
, servant-client
|
, servant-client
|
||||||
, servant-server >= 0.2.1
|
, servant-server >= 0.2.1
|
||||||
|
|
|
@ -210,7 +210,7 @@ instance (KnownSymbol sym, ToText a, HasClient sublayout)
|
||||||
-- if mparam = Nothing, we don't add it to the query string
|
-- if mparam = Nothing, we don't add it to the query string
|
||||||
clientWithRoute Proxy req mparam =
|
clientWithRoute Proxy req mparam =
|
||||||
clientWithRoute (Proxy :: Proxy sublayout) $
|
clientWithRoute (Proxy :: Proxy sublayout) $
|
||||||
appendToQueryString pname mparamText req
|
maybe req (flip (appendToQueryString pname) req . Just) mparamText
|
||||||
|
|
||||||
where pname = cs pname'
|
where pname = cs pname'
|
||||||
pname' = symbolVal (Proxy :: Proxy sym)
|
pname' = symbolVal (Proxy :: Proxy sym)
|
||||||
|
@ -251,7 +251,7 @@ instance (KnownSymbol sym, ToText a, HasClient sublayout)
|
||||||
|
|
||||||
clientWithRoute Proxy req paramlist =
|
clientWithRoute Proxy req paramlist =
|
||||||
clientWithRoute (Proxy :: Proxy sublayout) $
|
clientWithRoute (Proxy :: Proxy sublayout) $
|
||||||
foldl' (\ value req' -> appendToQueryString pname req' value) req paramlist'
|
foldl' (\ req' -> maybe req' (flip (appendToQueryString pname) req' . Just)) req paramlist'
|
||||||
|
|
||||||
where pname = cs pname'
|
where pname = cs pname'
|
||||||
pname' = symbolVal (Proxy :: Proxy sym)
|
pname' = symbolVal (Proxy :: Proxy sym)
|
||||||
|
@ -292,6 +292,121 @@ instance (KnownSymbol sym, HasClient sublayout)
|
||||||
|
|
||||||
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
|
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
|
||||||
|
|
||||||
|
-- | 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
|
||||||
|
|
||||||
|
type Client (MatrixParam sym a :> sublayout) =
|
||||||
|
Maybe a -> Client sublayout
|
||||||
|
|
||||||
|
-- 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
|
||||||
|
|
||||||
|
type Client (MatrixParams sym a :> sublayout) =
|
||||||
|
[a] -> Client sublayout
|
||||||
|
|
||||||
|
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
|
||||||
|
|
||||||
|
type Client (MatrixFlag sym :> sublayout) =
|
||||||
|
Bool -> Client sublayout
|
||||||
|
|
||||||
|
clientWithRoute Proxy req flag =
|
||||||
|
clientWithRoute (Proxy :: Proxy sublayout) $
|
||||||
|
if flag
|
||||||
|
then appendToMatrixParams paramname Nothing req
|
||||||
|
else req
|
||||||
|
|
||||||
|
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
|
||||||
|
|
||||||
-- | Pick a 'Method' and specify where the server you want to query is. You get
|
-- | Pick a 'Method' and specify where the server you want to query is. You get
|
||||||
-- back the status code and the response body as a 'ByteString'.
|
-- back the status code and the response body as a 'ByteString'.
|
||||||
instance HasClient Raw where
|
instance HasClient Raw where
|
||||||
|
|
|
@ -41,6 +41,13 @@ appendToPath :: String -> Req -> Req
|
||||||
appendToPath p req =
|
appendToPath p req =
|
||||||
req { reqPath = reqPath req ++ "/" ++ p }
|
req { reqPath = reqPath req ++ "/" ++ p }
|
||||||
|
|
||||||
|
appendToMatrixParams :: String
|
||||||
|
-> Maybe String
|
||||||
|
-> Req
|
||||||
|
-> Req
|
||||||
|
appendToMatrixParams pname pvalue req =
|
||||||
|
req { reqPath = reqPath req ++ ";" ++ pname ++ maybe "" ("=" ++) pvalue }
|
||||||
|
|
||||||
appendToQueryString :: Text -- ^ param name
|
appendToQueryString :: Text -- ^ param name
|
||||||
-> Maybe Text -- ^ param value
|
-> Maybe Text -- ^ param value
|
||||||
-> Req
|
-> Req
|
||||||
|
|
|
@ -4,7 +4,7 @@
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# OPTIONS_GHC -fcontext-stack=25 #-}
|
||||||
module Servant.ClientSpec where
|
module Servant.ClientSpec where
|
||||||
|
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
|
@ -50,6 +50,9 @@ type Api =
|
||||||
:<|> "param" :> QueryParam "name" String :> Get Person
|
:<|> "param" :> QueryParam "name" String :> Get Person
|
||||||
:<|> "params" :> QueryParams "names" String :> Get [Person]
|
:<|> "params" :> QueryParams "names" String :> Get [Person]
|
||||||
:<|> "flag" :> QueryFlag "flag" :> Get Bool
|
:<|> "flag" :> QueryFlag "flag" :> Get Bool
|
||||||
|
:<|> "matrixparam" :> MatrixParam "name" String :> Get Person
|
||||||
|
:<|> "matrixparams" :> MatrixParams "name" String :> Get [Person]
|
||||||
|
:<|> "matrixflag" :> MatrixFlag "flag" :> Get Bool
|
||||||
:<|> "rawSuccess" :> Raw
|
:<|> "rawSuccess" :> Raw
|
||||||
:<|> "rawFailure" :> Raw
|
:<|> "rawFailure" :> Raw
|
||||||
:<|> "multiple" :>
|
:<|> "multiple" :>
|
||||||
|
@ -72,6 +75,12 @@ server = serve api (
|
||||||
Nothing -> left (400, "missing parameter"))
|
Nothing -> left (400, "missing parameter"))
|
||||||
:<|> (\ names -> return (zipWith Person names [0..]))
|
:<|> (\ names -> return (zipWith Person names [0..]))
|
||||||
:<|> return
|
:<|> return
|
||||||
|
:<|> (\ name -> case name of
|
||||||
|
Just "alice" -> return alice
|
||||||
|
Just name -> left (400, name ++ " not found")
|
||||||
|
Nothing -> left (400, "missing parameter"))
|
||||||
|
:<|> (\ names -> return (zipWith Person names [0..]))
|
||||||
|
:<|> return
|
||||||
:<|> (\ _request respond -> respond $ responseLBS ok200 [] "rawSuccess")
|
:<|> (\ _request respond -> respond $ responseLBS ok200 [] "rawSuccess")
|
||||||
:<|> (\ _request respond -> respond $ responseLBS badRequest400 [] "rawFailure")
|
:<|> (\ _request respond -> respond $ responseLBS badRequest400 [] "rawFailure")
|
||||||
:<|> \ a b c d -> return (a, b, c, d)
|
:<|> \ a b c d -> return (a, b, c, d)
|
||||||
|
@ -86,6 +95,9 @@ getBody :: Person -> BaseUrl -> EitherT String IO Person
|
||||||
getQueryParam :: Maybe String -> BaseUrl -> EitherT String IO Person
|
getQueryParam :: Maybe String -> BaseUrl -> EitherT String IO Person
|
||||||
getQueryParams :: [String] -> BaseUrl -> EitherT String IO [Person]
|
getQueryParams :: [String] -> BaseUrl -> EitherT String IO [Person]
|
||||||
getQueryFlag :: Bool -> BaseUrl -> EitherT String IO Bool
|
getQueryFlag :: Bool -> BaseUrl -> EitherT String IO Bool
|
||||||
|
getMatrixParam :: Maybe String -> BaseUrl -> EitherT String IO Person
|
||||||
|
getMatrixParams :: [String] -> BaseUrl -> EitherT String IO [Person]
|
||||||
|
getMatrixFlag :: Bool -> BaseUrl -> EitherT String IO Bool
|
||||||
getRawSuccess :: Method -> BaseUrl -> EitherT String IO (Int, ByteString)
|
getRawSuccess :: Method -> BaseUrl -> EitherT String IO (Int, ByteString)
|
||||||
getRawFailure :: Method -> BaseUrl -> EitherT String IO (Int, ByteString)
|
getRawFailure :: Method -> BaseUrl -> EitherT String IO (Int, ByteString)
|
||||||
getMultiple :: String -> Maybe Int -> Bool -> [(String, [Rational])]
|
getMultiple :: String -> Maybe Int -> Bool -> [(String, [Rational])]
|
||||||
|
@ -97,6 +109,9 @@ getMultiple :: String -> Maybe Int -> Bool -> [(String, [Rational])]
|
||||||
:<|> getQueryParam
|
:<|> getQueryParam
|
||||||
:<|> getQueryParams
|
:<|> getQueryParams
|
||||||
:<|> getQueryFlag
|
:<|> getQueryFlag
|
||||||
|
:<|> getMatrixParam
|
||||||
|
:<|> getMatrixParams
|
||||||
|
:<|> getMatrixFlag
|
||||||
:<|> getRawSuccess
|
:<|> getRawSuccess
|
||||||
:<|> getRawFailure
|
:<|> getRawFailure
|
||||||
:<|> getMultiple)
|
:<|> getMultiple)
|
||||||
|
@ -129,6 +144,21 @@ spec = do
|
||||||
it (show flag) $ withServer $ \ host -> do
|
it (show flag) $ withServer $ \ host -> do
|
||||||
runEitherT (getQueryFlag flag host) `shouldReturn` Right flag
|
runEitherT (getQueryFlag flag host) `shouldReturn` Right flag
|
||||||
|
|
||||||
|
it "Servant.API.MatrixParam" $ withServer $ \ host -> do
|
||||||
|
runEitherT (getMatrixParam (Just "alice") host) `shouldReturn` Right alice
|
||||||
|
Left result <- runEitherT (getMatrixParam (Just "bob") host)
|
||||||
|
result `shouldContain` "bob not found"
|
||||||
|
|
||||||
|
it "Servant.API.MatrixParam.MatrixParams" $ withServer $ \ host -> do
|
||||||
|
runEitherT (getMatrixParams [] host) `shouldReturn` Right []
|
||||||
|
runEitherT (getMatrixParams ["alice", "bob"] host)
|
||||||
|
`shouldReturn` Right [Person "alice" 0, Person "bob" 1]
|
||||||
|
|
||||||
|
context "Servant.API.MatrixParam.MatrixFlag" $
|
||||||
|
forM_ [False, True] $ \ flag ->
|
||||||
|
it (show flag) $ withServer $ \ host -> do
|
||||||
|
runEitherT (getMatrixFlag flag host) `shouldReturn` Right flag
|
||||||
|
|
||||||
it "Servant.API.Raw on success" $ withServer $ \ host -> do
|
it "Servant.API.Raw on success" $ withServer $ \ host -> do
|
||||||
runEitherT (getRawSuccess methodGet host) `shouldReturn` Right (200, "rawSuccess")
|
runEitherT (getRawSuccess methodGet host) `shouldReturn` Right (200, "rawSuccess")
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue