Write tests for Optional ReqBody' and fix some cases
This commit is contained in:
parent
a6be2ee728
commit
a2c0a55535
2 changed files with 42 additions and 17 deletions
|
@ -49,8 +49,6 @@ import qualified Data.ByteString.Lazy as BL
|
||||||
import Data.Constraint (Constraint, Dict(..))
|
import Data.Constraint (Constraint, Dict(..))
|
||||||
import Data.Either
|
import Data.Either
|
||||||
(partitionEithers)
|
(partitionEithers)
|
||||||
import Data.Function
|
|
||||||
((&))
|
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
(fromMaybe, isNothing, mapMaybe, maybeToList)
|
(fromMaybe, isNothing, mapMaybe, maybeToList)
|
||||||
import Data.String
|
import Data.String
|
||||||
|
@ -681,9 +679,7 @@ instance ( AllCTUnrender list a, HasServer api context
|
||||||
Just f -> return f
|
Just f -> return f
|
||||||
|
|
||||||
-- Body check, we get a body parsing functions as the first argument.
|
-- Body check, we get a body parsing functions as the first argument.
|
||||||
bodyCheck f = withRequest $ \ request -> do
|
bodyCheck f = withRequest $ \ request ->
|
||||||
mrqbody <- f <$> liftIO (lazyRequestBody request)
|
|
||||||
|
|
||||||
let
|
let
|
||||||
hasReqBody =
|
hasReqBody =
|
||||||
case requestBodyLength request of
|
case requestBodyLength request of
|
||||||
|
@ -692,13 +688,15 @@ instance ( AllCTUnrender list a, HasServer api context
|
||||||
|
|
||||||
serverErr :: String -> ServerError
|
serverErr :: String -> ServerError
|
||||||
serverErr = formatError rep request . cs
|
serverErr = formatError rep request . cs
|
||||||
|
in
|
||||||
mrqbody & case (sbool :: SBool (FoldRequired mods), sbool :: SBool (FoldLenient mods), hasReqBody) of
|
fmap f (liftIO $ lazyRequestBody request) >>=
|
||||||
(STrue, STrue, _) -> return . bimap cs id
|
case (sbool :: SBool (FoldRequired mods), sbool :: SBool (FoldLenient mods), hasReqBody) of
|
||||||
(STrue, SFalse, _) -> either (delayedFailFatal . serverErr) return
|
(STrue, STrue, _) -> return . bimap cs id
|
||||||
(SFalse, _, False) -> return . const Nothing
|
(STrue, SFalse, _) -> either (delayedFailFatal . serverErr) return
|
||||||
(SFalse, STrue, True) -> return . Just . bimap cs id
|
(SFalse, STrue, False) -> return . either (const Nothing) (Just . Right)
|
||||||
(SFalse, SFalse, True) -> either (delayedFailFatal . serverErr) (return . Just)
|
(SFalse, SFalse, False) -> return . either (const Nothing) Just
|
||||||
|
(SFalse, STrue, True) -> return . Just . bimap cs id
|
||||||
|
(SFalse, SFalse, True) -> either (delayedFailFatal . serverErr) (return . Just)
|
||||||
|
|
||||||
instance
|
instance
|
||||||
( FramingUnrender framing, FromSourceIO chunk a, MimeUnrender ctype chunk
|
( FramingUnrender framing, FromSourceIO chunk a, MimeUnrender ctype chunk
|
||||||
|
|
|
@ -51,10 +51,11 @@ import Servant.API
|
||||||
BasicAuthData (BasicAuthData), Capture, Capture', CaptureAll,
|
BasicAuthData (BasicAuthData), Capture, Capture', CaptureAll,
|
||||||
Delete, EmptyAPI, Fragment, Get, HasStatus (StatusOf), Header,
|
Delete, EmptyAPI, Fragment, Get, HasStatus (StatusOf), Header,
|
||||||
Headers, HttpVersion, IsSecure (..), JSON, Lenient,
|
Headers, HttpVersion, IsSecure (..), JSON, Lenient,
|
||||||
NoContent (..), NoContentVerb, NoFraming, OctetStream, Patch,
|
NoContent (..), NoContentVerb, NoFraming, OctetStream,
|
||||||
PlainText, Post, Put, QueryFlag, QueryParam, QueryParams, Raw,
|
Optional, Patch, PlainText, Post, Put, QueryFlag, QueryParam,
|
||||||
RemoteHost, ReqBody, SourceIO, StdMethod (..), Stream, Strict,
|
QueryParams, Raw, RemoteHost, ReqBody, ReqBody', SourceIO,
|
||||||
UVerb, Union, Verb, WithStatus (..), addHeader)
|
StdMethod (..), Stream, Strict, UVerb, Union, Verb,
|
||||||
|
WithStatus (..), addHeader)
|
||||||
import Servant.Server
|
import Servant.Server
|
||||||
(Context ((:.), EmptyContext), Handler, Server, Tagged (..),
|
(Context ((:.), EmptyContext), Handler, Server, Tagged (..),
|
||||||
emptyServer, err401, err403, err404, respond, serve,
|
emptyServer, err401, err403, err404, respond, serve,
|
||||||
|
@ -501,6 +502,7 @@ fragmentSpec = do
|
||||||
------------------------------------------------------------------------------
|
------------------------------------------------------------------------------
|
||||||
type ReqBodyApi = ReqBody '[JSON] Person :> Post '[JSON] Person
|
type ReqBodyApi = ReqBody '[JSON] Person :> Post '[JSON] Person
|
||||||
:<|> "blah" :> ReqBody '[JSON] Person :> Put '[JSON] Integer
|
:<|> "blah" :> ReqBody '[JSON] Person :> Put '[JSON] Integer
|
||||||
|
:<|> "meh" :> ReqBody' '[Optional, Strict] '[JSON] Person :> Put '[JSON] Integer
|
||||||
|
|
||||||
reqBodyApi :: Proxy ReqBodyApi
|
reqBodyApi :: Proxy ReqBodyApi
|
||||||
reqBodyApi = Proxy
|
reqBodyApi = Proxy
|
||||||
|
@ -509,7 +511,7 @@ reqBodySpec :: Spec
|
||||||
reqBodySpec = describe "Servant.API.ReqBody" $ do
|
reqBodySpec = describe "Servant.API.ReqBody" $ do
|
||||||
|
|
||||||
let server :: Server ReqBodyApi
|
let server :: Server ReqBodyApi
|
||||||
server = return :<|> return . age
|
server = return :<|> return . age :<|> return . maybe 0 age
|
||||||
mkReq method x = THW.request method x
|
mkReq method x = THW.request method x
|
||||||
[(hContentType, "application/json;charset=utf-8")]
|
[(hContentType, "application/json;charset=utf-8")]
|
||||||
|
|
||||||
|
@ -526,6 +528,31 @@ reqBodySpec = describe "Servant.API.ReqBody" $ do
|
||||||
THW.request methodPost "/"
|
THW.request methodPost "/"
|
||||||
[(hContentType, "application/nonsense")] "" `shouldRespondWith` 415
|
[(hContentType, "application/nonsense")] "" `shouldRespondWith` 415
|
||||||
|
|
||||||
|
describe "optional request body" $ do
|
||||||
|
it "request without body succeeds" $ do
|
||||||
|
THW.request methodPut "/meh" [] mempty `shouldRespondWith` 200
|
||||||
|
|
||||||
|
it "request without body responds with proper default value" $ do
|
||||||
|
response <- THW.request methodPut "/meh" [] mempty
|
||||||
|
liftIO $ simpleBody response `shouldBe` encode (0 :: Integer)
|
||||||
|
|
||||||
|
it "responds with 415 if the request body media type is unsupported" $ do
|
||||||
|
THW.request methodPut "/meh" [(hContentType, "application/nonsense")]
|
||||||
|
(encode alice) `shouldRespondWith` 415
|
||||||
|
THW.request methodPut "/meh" [(hContentType, "application/octet-stream")]
|
||||||
|
(encode alice) `shouldRespondWith` 415
|
||||||
|
|
||||||
|
it "request without body and with content-type header succeeds" $ do
|
||||||
|
mkReq methodPut "/meh" mempty `shouldRespondWith` 200
|
||||||
|
|
||||||
|
it "request without body and with content-type header returns default value" $ do
|
||||||
|
response <- mkReq methodPut "/meh" mempty
|
||||||
|
liftIO $ simpleBody response `shouldBe` encode (0 :: Integer)
|
||||||
|
|
||||||
|
it "optional request body can be provided" $ do
|
||||||
|
response <- mkReq methodPut "/meh" (encode alice)
|
||||||
|
liftIO $ simpleBody response `shouldBe` encode (age alice)
|
||||||
|
|
||||||
-- }}}
|
-- }}}
|
||||||
------------------------------------------------------------------------------
|
------------------------------------------------------------------------------
|
||||||
-- * headerSpec {{{
|
-- * headerSpec {{{
|
||||||
|
|
Loading…
Add table
Reference in a new issue