Skip to content

Commit 50b50fa

Browse files
committed
Write tests for Optional ReqBody' and fix some cases
1 parent 32db412 commit 50b50fa

File tree

2 files changed

+41
-16
lines changed

2 files changed

+41
-16
lines changed

servant-server/src/Servant/Server/Internal.hs

Lines changed: 10 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -48,8 +48,6 @@ import qualified Data.ByteString.Char8 as BC8
4848
import qualified Data.ByteString.Lazy as BL
4949
import Data.Either
5050
(partitionEithers)
51-
import Data.Function
52-
((&))
5351
import Data.Maybe
5452
(fromMaybe, isNothing, mapMaybe, maybeToList)
5553
import Data.Semigroup
@@ -674,9 +672,7 @@ instance ( AllCTUnrender list a, HasServer api context
674672
Just f -> return f
675673

676674
-- Body check, we get a body parsing functions as the first argument.
677-
bodyCheck f = withRequest $ \ request -> do
678-
mrqbody <- f <$> liftIO (lazyRequestBody request)
679-
675+
bodyCheck f = withRequest $ \ request ->
680676
let
681677
hasReqBody =
682678
case requestBodyLength request of
@@ -685,13 +681,15 @@ instance ( AllCTUnrender list a, HasServer api context
685681

686682
serverErr :: String -> ServerError
687683
serverErr = formatError rep request . cs
688-
689-
mrqbody & case (sbool :: SBool (FoldRequired mods), sbool :: SBool (FoldLenient mods), hasReqBody) of
690-
(STrue, STrue, _) -> return . bimap cs id
691-
(STrue, SFalse, _) -> either (delayedFailFatal . serverErr) return
692-
(SFalse, _, False) -> return . const Nothing
693-
(SFalse, STrue, True) -> return . Just . bimap cs id
694-
(SFalse, SFalse, True) -> either (delayedFailFatal . serverErr) (return . Just)
684+
in
685+
fmap f (liftIO $ lazyRequestBody request) >>=
686+
case (sbool :: SBool (FoldRequired mods), sbool :: SBool (FoldLenient mods), hasReqBody) of
687+
(STrue, STrue, _) -> return . bimap cs id
688+
(STrue, SFalse, _) -> either (delayedFailFatal . serverErr) return
689+
(SFalse, STrue, False) -> return . either (const Nothing) (Just . Right)
690+
(SFalse, SFalse, False) -> return . either (const Nothing) Just
691+
(SFalse, STrue, True) -> return . Just . bimap cs id
692+
(SFalse, SFalse, True) -> either (delayedFailFatal . serverErr) (return . Just)
695693

696694
instance
697695
( FramingUnrender framing, FromSourceIO chunk a, MimeUnrender ctype chunk

servant-server/test/Servant/ServerSpec.hs

Lines changed: 31 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -51,9 +51,10 @@ import Servant.API
5151
BasicAuthData (BasicAuthData), Capture, Capture', CaptureAll,
5252
Delete, EmptyAPI, Get, Header, Headers, HttpVersion,
5353
IsSecure (..), JSON, Lenient, NoContent (..), NoContentVerb,
54-
NoFraming, OctetStream, Patch, PlainText, Post, Put,
55-
QueryFlag, QueryParam, QueryParams, Raw, RemoteHost, ReqBody,
56-
SourceIO, StdMethod (..), Stream, Strict, Verb, addHeader)
54+
NoFraming, OctetStream, Optional, Patch, PlainText, Post, Put,
55+
QueryFlag, QueryParam, QueryParams, Raw, RemoteHost,
56+
ReqBody, ReqBody', SourceIO, StdMethod (..), Stream, Strict,
57+
Verb, addHeader)
5758
import Servant.Server
5859
(Context ((:.), EmptyContext), Handler, Server, Tagged (..),
5960
emptyServer, err401, err403, err404, serve, serveWithContext)
@@ -465,6 +466,7 @@ queryParamSpec = do
465466
------------------------------------------------------------------------------
466467
type ReqBodyApi = ReqBody '[JSON] Person :> Post '[JSON] Person
467468
:<|> "blah" :> ReqBody '[JSON] Person :> Put '[JSON] Integer
469+
:<|> "meh" :> ReqBody' '[Optional, Strict] '[JSON] Person :> Put '[JSON] Integer
468470

469471
reqBodyApi :: Proxy ReqBodyApi
470472
reqBodyApi = Proxy
@@ -473,7 +475,7 @@ reqBodySpec :: Spec
473475
reqBodySpec = describe "Servant.API.ReqBody" $ do
474476

475477
let server :: Server ReqBodyApi
476-
server = return :<|> return . age
478+
server = return :<|> return . age :<|> return . maybe 0 age
477479
mkReq method x = THW.request method x
478480
[(hContentType, "application/json;charset=utf-8")]
479481

@@ -490,6 +492,31 @@ reqBodySpec = describe "Servant.API.ReqBody" $ do
490492
THW.request methodPost "/"
491493
[(hContentType, "application/nonsense")] "" `shouldRespondWith` 415
492494

495+
describe "optional request body" $ do
496+
it "request without body succeeds" $ do
497+
THW.request methodPut "/meh" [] mempty `shouldRespondWith` 200
498+
499+
it "request without body responds with proper default value" $ do
500+
response <- THW.request methodPut "/meh" [] mempty
501+
liftIO $ simpleBody response `shouldBe` encode (0 :: Integer)
502+
503+
it "responds with 415 if the request body media type is unsupported" $ do
504+
THW.request methodPut "/meh" [(hContentType, "application/nonsense")]
505+
(encode alice) `shouldRespondWith` 415
506+
THW.request methodPut "/meh" [(hContentType, "application/octet-stream")]
507+
(encode alice) `shouldRespondWith` 415
508+
509+
it "request without body and with content-type header succeeds" $ do
510+
mkReq methodPut "/meh" mempty `shouldRespondWith` 200
511+
512+
it "request without body and with content-type header returns default value" $ do
513+
response <- mkReq methodPut "/meh" mempty
514+
liftIO $ simpleBody response `shouldBe` encode (0 :: Integer)
515+
516+
it "optional request body can be provided" $ do
517+
response <- mkReq methodPut "/meh" (encode alice)
518+
liftIO $ simpleBody response `shouldBe` encode (age alice)
519+
493520
-- }}}
494521
------------------------------------------------------------------------------
495522
-- * headerSpec {{{

0 commit comments

Comments
 (0)