Merge pull request #72 from codedmart/deleteFix
Allow zero content types on delete. fixes #69
This commit is contained in:
commit
3e10ee8a69
3 changed files with 31 additions and 16 deletions
|
@ -1,3 +1,7 @@
|
||||||
|
0.4.1
|
||||||
|
-----
|
||||||
|
* The `HasClient` instance for `Delete cts ()` now does not care at all about content types provided.
|
||||||
|
|
||||||
0.4
|
0.4
|
||||||
---
|
---
|
||||||
* `Delete` now is like `Get`, `Post`, `Put`, and `Patch` and returns a response body
|
* `Delete` now is like `Get`, `Post`, `Put`, and `Patch` and returns a response body
|
||||||
|
|
|
@ -7,6 +7,7 @@
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
#if !MIN_VERSION_base(4,8,0)
|
#if !MIN_VERSION_base(4,8,0)
|
||||||
{-# LANGUAGE OverlappingInstances #-}
|
{-# LANGUAGE OverlappingInstances #-}
|
||||||
#endif
|
#endif
|
||||||
|
@ -126,8 +127,9 @@ instance
|
||||||
#if MIN_VERSION_base(4,8,0)
|
#if MIN_VERSION_base(4,8,0)
|
||||||
{-# OVERLAPPABLE #-}
|
{-# OVERLAPPABLE #-}
|
||||||
#endif
|
#endif
|
||||||
(MimeUnrender ct a) => HasClient (Delete (ct ': cts) a) where
|
-- See https://downloads.haskell.org/~ghc/7.8.2/docs/html/users_guide/type-class-extensions.html#undecidable-instances
|
||||||
type Client (Delete (ct ': cts) a) = EitherT ServantError IO a
|
(MimeUnrender ct a, cts' ~ (ct ': cts)) => HasClient (Delete cts' a) where
|
||||||
|
type Client (Delete cts' a) = EitherT ServantError IO a
|
||||||
clientWithRoute Proxy req baseurl =
|
clientWithRoute Proxy req baseurl =
|
||||||
snd <$> performRequestCT (Proxy :: Proxy ct) H.methodDelete req [200, 202] baseurl
|
snd <$> performRequestCT (Proxy :: Proxy ct) H.methodDelete req [200, 202] baseurl
|
||||||
|
|
||||||
|
@ -137,8 +139,8 @@ instance
|
||||||
#if MIN_VERSION_base(4,8,0)
|
#if MIN_VERSION_base(4,8,0)
|
||||||
{-# OVERLAPPING #-}
|
{-# OVERLAPPING #-}
|
||||||
#endif
|
#endif
|
||||||
HasClient (Delete (ct ': cts) ()) where
|
HasClient (Delete cts ()) where
|
||||||
type Client (Delete (ct ': cts) ()) = EitherT ServantError IO ()
|
type Client (Delete cts ()) = EitherT ServantError IO ()
|
||||||
clientWithRoute Proxy req baseurl =
|
clientWithRoute Proxy req baseurl =
|
||||||
void $ performRequestNoBody H.methodDelete req [204] baseurl
|
void $ performRequestNoBody H.methodDelete req [204] baseurl
|
||||||
|
|
||||||
|
@ -148,9 +150,10 @@ instance
|
||||||
#if MIN_VERSION_base(4,8,0)
|
#if MIN_VERSION_base(4,8,0)
|
||||||
{-# OVERLAPPING #-}
|
{-# OVERLAPPING #-}
|
||||||
#endif
|
#endif
|
||||||
( MimeUnrender ct a, BuildHeadersTo ls
|
-- See https://downloads.haskell.org/~ghc/7.8.2/docs/html/users_guide/type-class-extensions.html#undecidable-instances
|
||||||
) => HasClient (Delete (ct ': cts) (Headers ls a)) where
|
( MimeUnrender ct a, BuildHeadersTo ls, cts' ~ (ct ': cts)
|
||||||
type Client (Delete (ct ': cts) (Headers ls a)) = EitherT ServantError IO (Headers ls a)
|
) => HasClient (Delete cts' (Headers ls a)) where
|
||||||
|
type Client (Delete cts' (Headers ls a)) = EitherT ServantError IO (Headers ls a)
|
||||||
clientWithRoute Proxy req baseurl = do
|
clientWithRoute Proxy req baseurl = do
|
||||||
(hdrs, resp) <- performRequestCT (Proxy :: Proxy ct) H.methodDelete req [200, 202] baseurl
|
(hdrs, resp) <- performRequestCT (Proxy :: Proxy ct) H.methodDelete req [200, 202] baseurl
|
||||||
return $ Headers { getResponse = resp
|
return $ Headers { getResponse = resp
|
||||||
|
|
|
@ -80,7 +80,7 @@ type TestHeaders = '[Header "X-Example1" Int, Header "X-Example2" String]
|
||||||
|
|
||||||
type Api =
|
type Api =
|
||||||
"get" :> Get '[JSON] Person
|
"get" :> Get '[JSON] Person
|
||||||
:<|> "delete" :> Delete '[JSON] ()
|
:<|> "deleteEmpty" :> Delete '[] ()
|
||||||
:<|> "capture" :> Capture "name" String :> Get '[JSON,FormUrlEncoded] Person
|
:<|> "capture" :> Capture "name" String :> Get '[JSON,FormUrlEncoded] Person
|
||||||
:<|> "body" :> ReqBody '[FormUrlEncoded,JSON] Person :> Post '[JSON] Person
|
:<|> "body" :> ReqBody '[FormUrlEncoded,JSON] Person :> Post '[JSON] Person
|
||||||
:<|> "param" :> QueryParam "name" String :> Get '[FormUrlEncoded,JSON] Person
|
:<|> "param" :> QueryParam "name" String :> Get '[FormUrlEncoded,JSON] Person
|
||||||
|
@ -98,6 +98,7 @@ type Api =
|
||||||
ReqBody '[JSON] [(String, [Rational])] :>
|
ReqBody '[JSON] [(String, [Rational])] :>
|
||||||
Get '[JSON] (String, Maybe Int, Bool, [(String, [Rational])])
|
Get '[JSON] (String, Maybe Int, Bool, [(String, [Rational])])
|
||||||
:<|> "headers" :> Get '[JSON] (Headers TestHeaders Bool)
|
:<|> "headers" :> Get '[JSON] (Headers TestHeaders Bool)
|
||||||
|
:<|> "deleteContentType" :> Delete '[JSON] ()
|
||||||
api :: Proxy Api
|
api :: Proxy Api
|
||||||
api = Proxy
|
api = Proxy
|
||||||
|
|
||||||
|
@ -123,6 +124,7 @@ server = serve api (
|
||||||
:<|> (\ _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))
|
||||||
:<|> (return $ addHeader 1729 $ addHeader "eg2" True)
|
:<|> (return $ addHeader 1729 $ addHeader "eg2" True)
|
||||||
|
:<|> return ()
|
||||||
)
|
)
|
||||||
|
|
||||||
withServer :: (BaseUrl -> IO a) -> IO a
|
withServer :: (BaseUrl -> IO a) -> IO a
|
||||||
|
@ -148,7 +150,7 @@ withFailServer action = withWaiDaemon (return failServer) action
|
||||||
spec :: IO ()
|
spec :: IO ()
|
||||||
spec = withServer $ \ baseUrl -> do
|
spec = withServer $ \ baseUrl -> do
|
||||||
let getGet :: EitherT ServantError IO Person
|
let getGet :: EitherT ServantError IO Person
|
||||||
getDelete :: EitherT ServantError IO ()
|
getDeleteEmpty :: EitherT ServantError IO ()
|
||||||
getCapture :: String -> EitherT ServantError IO Person
|
getCapture :: String -> EitherT ServantError IO Person
|
||||||
getBody :: Person -> EitherT ServantError IO Person
|
getBody :: Person -> EitherT ServantError IO Person
|
||||||
getQueryParam :: Maybe String -> EitherT ServantError IO Person
|
getQueryParam :: Maybe String -> EitherT ServantError IO Person
|
||||||
|
@ -161,8 +163,9 @@ spec = withServer $ \ baseUrl -> do
|
||||||
getRawFailure :: Method -> EitherT ServantError IO (Int, ByteString, MediaType, [HTTP.Header], C.Response ByteString)
|
getRawFailure :: Method -> EitherT ServantError IO (Int, ByteString, MediaType, [HTTP.Header], C.Response ByteString)
|
||||||
getMultiple :: String -> Maybe Int -> Bool -> [(String, [Rational])] -> EitherT ServantError IO (String, Maybe Int, Bool, [(String, [Rational])])
|
getMultiple :: String -> Maybe Int -> Bool -> [(String, [Rational])] -> EitherT ServantError IO (String, Maybe Int, Bool, [(String, [Rational])])
|
||||||
getRespHeaders :: EitherT ServantError IO (Headers TestHeaders Bool)
|
getRespHeaders :: EitherT ServantError IO (Headers TestHeaders Bool)
|
||||||
|
getDeleteContentType :: EitherT ServantError IO ()
|
||||||
( getGet
|
( getGet
|
||||||
:<|> getDelete
|
:<|> getDeleteEmpty
|
||||||
:<|> getCapture
|
:<|> getCapture
|
||||||
:<|> getBody
|
:<|> getBody
|
||||||
:<|> getQueryParam
|
:<|> getQueryParam
|
||||||
|
@ -174,15 +177,20 @@ spec = withServer $ \ baseUrl -> do
|
||||||
:<|> getRawSuccess
|
:<|> getRawSuccess
|
||||||
:<|> getRawFailure
|
:<|> getRawFailure
|
||||||
:<|> getMultiple
|
:<|> getMultiple
|
||||||
:<|> getRespHeaders)
|
:<|> getRespHeaders
|
||||||
|
:<|> getDeleteContentType)
|
||||||
= client api baseUrl
|
= client api baseUrl
|
||||||
|
|
||||||
hspec $ do
|
hspec $ do
|
||||||
it "Servant.API.Get" $ do
|
it "Servant.API.Get" $ do
|
||||||
(Arrow.left show <$> runEitherT getGet) `shouldReturn` Right alice
|
(Arrow.left show <$> runEitherT getGet) `shouldReturn` Right alice
|
||||||
|
|
||||||
it "Servant.API.Delete" $ do
|
describe "Servant.API.Delete" $ do
|
||||||
(Arrow.left show <$> runEitherT getDelete) `shouldReturn` Right ()
|
it "allows empty content type" $ do
|
||||||
|
(Arrow.left show <$> runEitherT getDeleteEmpty) `shouldReturn` Right ()
|
||||||
|
|
||||||
|
it "allows content type" $ do
|
||||||
|
(Arrow.left show <$> runEitherT getDeleteContentType) `shouldReturn` Right ()
|
||||||
|
|
||||||
it "Servant.API.Capture" $ do
|
it "Servant.API.Capture" $ do
|
||||||
(Arrow.left show <$> runEitherT (getCapture "Paula")) `shouldReturn` Right (Person "Paula" 0)
|
(Arrow.left show <$> runEitherT (getCapture "Paula")) `shouldReturn` Right (Person "Paula" 0)
|
||||||
|
@ -274,11 +282,11 @@ spec = withServer $ \ baseUrl -> do
|
||||||
failSpec :: IO ()
|
failSpec :: IO ()
|
||||||
failSpec = withFailServer $ \ baseUrl -> do
|
failSpec = withFailServer $ \ baseUrl -> do
|
||||||
let getGet :: EitherT ServantError IO Person
|
let getGet :: EitherT ServantError IO Person
|
||||||
getDelete :: EitherT ServantError IO ()
|
getDeleteEmpty :: EitherT ServantError IO ()
|
||||||
getCapture :: String -> EitherT ServantError IO Person
|
getCapture :: String -> EitherT ServantError IO Person
|
||||||
getBody :: Person -> EitherT ServantError IO Person
|
getBody :: Person -> EitherT ServantError IO Person
|
||||||
( getGet
|
( getGet
|
||||||
:<|> getDelete
|
:<|> getDeleteEmpty
|
||||||
:<|> getCapture
|
:<|> getCapture
|
||||||
:<|> getBody
|
:<|> getBody
|
||||||
:<|> _ )
|
:<|> _ )
|
||||||
|
@ -289,7 +297,7 @@ failSpec = withFailServer $ \ baseUrl -> do
|
||||||
hspec $ do
|
hspec $ do
|
||||||
context "client returns errors appropriately" $ do
|
context "client returns errors appropriately" $ do
|
||||||
it "reports FailureResponse" $ do
|
it "reports FailureResponse" $ do
|
||||||
Left res <- runEitherT getDelete
|
Left res <- runEitherT getDeleteEmpty
|
||||||
case res of
|
case res of
|
||||||
FailureResponse (Status 404 "Not Found") _ _ -> return ()
|
FailureResponse (Status 404 "Not Found") _ _ -> return ()
|
||||||
_ -> fail $ "expected 404 response, but got " <> show res
|
_ -> fail $ "expected 404 response, but got " <> show res
|
||||||
|
|
Loading…
Reference in a new issue