Skip to content

Commit 32db412

Browse files
committed
Fix Optional ReqBody'
See #1346
1 parent 83bbc6d commit 32db412

File tree

1 file changed

+52
-20
lines changed

1 file changed

+52
-20
lines changed

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

Lines changed: 52 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -32,18 +32,24 @@ module Servant.Server.Internal
3232
, module Servant.Server.Internal.ServerError
3333
) where
3434

35+
import Control.Applicative
36+
((<|>))
3537
import Control.Monad
3638
(join, when)
3739
import Control.Monad.Trans
3840
(liftIO)
3941
import Control.Monad.Trans.Resource
4042
(runResourceT)
43+
import Data.Bifunctor
44+
(bimap)
4145
import qualified Data.ByteString as B
4246
import qualified Data.ByteString.Builder as BB
4347
import qualified Data.ByteString.Char8 as BC8
4448
import qualified Data.ByteString.Lazy as BL
4549
import Data.Either
4650
(partitionEithers)
51+
import Data.Function
52+
((&))
4753
import Data.Maybe
4854
(fromMaybe, isNothing, mapMaybe, maybeToList)
4955
import Data.Semigroup
@@ -64,9 +70,11 @@ import Network.HTTP.Types hiding
6470
import Network.Socket
6571
(SockAddr)
6672
import Network.Wai
67-
(Application, Request, httpVersion, isSecure, lazyRequestBody,
68-
queryString, remoteHost, requestBody, requestHeaders,
69-
requestMethod, responseLBS, responseStream, vault)
73+
(Application, Request, RequestBodyLength (KnownLength),
74+
httpVersion, isSecure, lazyRequestBody, queryString, remoteHost,
75+
requestBody, requestBodyLength, requestHeaders, requestMethod,
76+
responseLBS, responseStream,
77+
vault)
7078
import Prelude ()
7179
import Prelude.Compat
7280
import Servant.API
@@ -624,12 +632,13 @@ instance HasServer Raw context where
624632
-- > server = postBook
625633
-- > where postBook :: Book -> Handler Book
626634
-- > postBook book = ...insert into your db...
627-
instance ( AllCTUnrender list a, HasServer api context, SBoolI (FoldLenient mods)
635+
instance ( AllCTUnrender list a, HasServer api context
636+
, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)
628637
, HasContextEntry (MkContextWithErrorFormatter context) ErrorFormatters
629638
) => HasServer (ReqBody' mods list a :> api) context where
630639

631640
type ServerT (ReqBody' mods list a :> api) m =
632-
If (FoldLenient mods) (Either String a) a -> ServerT api m
641+
RequestArgument mods a -> ServerT api m
633642

634643
hoistServerWithContext _ pc nt s = hoistServerWithContext (Proxy :: Proxy api) pc nt . s
635644

@@ -641,25 +650,48 @@ instance ( AllCTUnrender list a, HasServer api context, SBoolI (FoldLenient mods
641650
formatError = bodyParserErrorFormatter $ getContextEntry (mkContextWithErrorFormatter context)
642651

643652
-- Content-Type check, we only lookup we can try to parse the request body
644-
ctCheck = withRequest $ \ request -> do
645-
-- See HTTP RFC 2616, section 7.2.1
646-
-- http://www.w3.org/Protocols/rfc2616/rfc2616-sec7.html#sec7.2.1
647-
-- See also "W3C Internet Media Type registration, consistency of use"
648-
-- http://www.w3.org/2001/tag/2002/0129-mime
649-
let contentTypeH = fromMaybe "application/octet-stream"
650-
$ lookup hContentType $ requestHeaders request
651-
case canHandleCTypeH (Proxy :: Proxy list) (cs contentTypeH) :: Maybe (BL.ByteString -> Either String a) of
652-
Nothing -> delayedFail err415
653-
Just f -> return f
653+
ctCheck = withRequest $ \ request ->
654+
let
655+
contentTypeH = lookup hContentType $ requestHeaders request
656+
657+
-- See HTTP RFC 2616, section 7.2.1
658+
-- http://www.w3.org/Protocols/rfc2616/rfc2616-sec7.html#sec7.2.1
659+
-- See also "W3C Internet Media Type registration, consistency of use"
660+
-- http://www.w3.org/2001/tag/2002/0129-mime
661+
contentTypeH' = fromMaybe "application/octet-stream" contentTypeH
662+
663+
canHandleContentTypeH :: Maybe (BL.ByteString -> Either String a)
664+
canHandleContentTypeH = canHandleCTypeH (Proxy :: Proxy list) (cs contentTypeH')
665+
666+
-- In case ReqBody' is Optional and neither request body nor Content-Type header was provided.
667+
noOptionalReqBody =
668+
case (sbool :: SBool (FoldRequired mods), contentTypeH, requestBodyLength request) of
669+
(SFalse, Nothing, KnownLength 0) -> Just . const $ Left "This value does not matter (it is ignored)"
670+
_ -> Nothing
671+
in
672+
case canHandleContentTypeH <|> noOptionalReqBody of
673+
Nothing -> delayedFail err415
674+
Just f -> return f
654675

655676
-- Body check, we get a body parsing functions as the first argument.
656677
bodyCheck f = withRequest $ \ request -> do
657678
mrqbody <- f <$> liftIO (lazyRequestBody request)
658-
case sbool :: SBool (FoldLenient mods) of
659-
STrue -> return mrqbody
660-
SFalse -> case mrqbody of
661-
Left e -> delayedFailFatal $ formatError rep request e
662-
Right v -> return v
679+
680+
let
681+
hasReqBody =
682+
case requestBodyLength request of
683+
KnownLength 0 -> False
684+
_ -> True
685+
686+
serverErr :: String -> ServerError
687+
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)
663695

664696
instance
665697
( FramingUnrender framing, FromSourceIO chunk a, MimeUnrender ctype chunk

0 commit comments

Comments
 (0)