Merge pull request #1156 from wireapp/feature/capture-lenient

Feature/capture lenient
This commit is contained in:
Oleg Grenrus 2019-03-27 01:15:49 +02:00 committed by GitHub
commit dc4125dcc4
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
4 changed files with 67 additions and 13 deletions

View File

@ -96,6 +96,28 @@
``` ```
## GET /capture-lenient/:foo
### Captures:
- *foo*: Capture foo Int
### Response:
- Status code 200
- Headers: []
- Supported content types are:
- `application/json;charset=utf-8`
- `application/json`
- Example (`application/json;charset=utf-8`, `application/json`):
```javascript
```
## GET /description ## GET /description
### foo ### foo

View File

@ -87,7 +87,7 @@ import Servant.API.ResponseHeaders
import qualified Servant.Types.SourceT as S import qualified Servant.Types.SourceT as S
import Web.HttpApiData import Web.HttpApiData
(FromHttpApiData, parseHeader, parseQueryParam, (FromHttpApiData, parseHeader, parseQueryParam,
parseUrlPieceMaybe, parseUrlPieces) parseUrlPieceMaybe, parseUrlPieces, parseUrlPiece)
import Servant.Server.Internal.BasicAuth import Servant.Server.Internal.BasicAuth
import Servant.Server.Internal.Context import Servant.Server.Internal.Context
@ -166,11 +166,11 @@ instance (HasServer a context, HasServer b context) => HasServer (a :<|> b) cont
-- > server = getBook -- > server = getBook
-- > where getBook :: Text -> Handler Book -- > where getBook :: Text -> Handler Book
-- > getBook isbn = ... -- > getBook isbn = ...
instance (KnownSymbol capture, FromHttpApiData a, HasServer api context) instance (KnownSymbol capture, FromHttpApiData a, HasServer api context, SBoolI (FoldLenient mods))
=> HasServer (Capture' mods capture a :> api) context where => HasServer (Capture' mods capture a :> api) context where
type ServerT (Capture' mods capture a :> api) m = type ServerT (Capture' mods capture a :> api) m =
a -> ServerT api m If (FoldLenient mods) (Either String a) a -> ServerT api m
hoistServerWithContext _ pc nt s = hoistServerWithContext (Proxy :: Proxy api) pc nt . s hoistServerWithContext _ pc nt s = hoistServerWithContext (Proxy :: Proxy api) pc nt . s
@ -178,9 +178,11 @@ instance (KnownSymbol capture, FromHttpApiData a, HasServer api context)
CaptureRouter $ CaptureRouter $
route (Proxy :: Proxy api) route (Proxy :: Proxy api)
context context
(addCapture d $ \ txt -> case parseUrlPieceMaybe txt of (addCapture d $ \ txt -> case ( sbool :: SBool (FoldLenient mods)
Nothing -> delayedFail err400 , parseUrlPiece txt :: Either T.Text a) of
Just v -> return v (SFalse, Left e) -> delayedFail err400 { errBody = cs e }
(SFalse, Right v) -> return v
(STrue, piece) -> return $ (either (Left . cs) Right) piece
) )
-- | If you use 'CaptureAll' in one of the endpoints for your API, -- | If you use 'CaptureAll' in one of the endpoints for your API,

View File

@ -46,7 +46,7 @@ import Network.Wai.Test
simpleHeaders, simpleStatus) simpleHeaders, simpleStatus)
import Servant.API import Servant.API
((:<|>) (..), (:>), AuthProtect, BasicAuth, ((:<|>) (..), (:>), AuthProtect, BasicAuth,
BasicAuthData (BasicAuthData), Capture, CaptureAll, Delete, BasicAuthData (BasicAuthData), Capture, Capture', CaptureAll, Lenient, Strict, Delete,
EmptyAPI, Get, Header, Headers, HttpVersion, IsSecure (..), EmptyAPI, Get, Header, Headers, HttpVersion, IsSecure (..),
JSON, NoContent (..), NoFraming, OctetStream, Patch, JSON, NoContent (..), NoFraming, OctetStream, Patch,
PlainText, Post, Put, QueryFlag, QueryParam, QueryParams, Raw, PlainText, Post, Put, QueryFlag, QueryParam, QueryParams, Raw,
@ -54,7 +54,7 @@ import Servant.API
addHeader) addHeader)
import Servant.Server import Servant.Server
(Context ((:.), EmptyContext), Handler, Server, Tagged (..), (Context ((:.), EmptyContext), Handler, Server, Tagged (..),
emptyServer, err401, err403, err404, serve, serveWithContext) emptyServer, err400, err401, err403, err404, serve, serveWithContext)
import Servant.Test.ComprehensiveAPI import Servant.Test.ComprehensiveAPI
import qualified Servant.Types.SourceT as S import qualified Servant.Types.SourceT as S
import Test.Hspec import Test.Hspec
@ -204,14 +204,28 @@ verbSpec = describe "Servant.API.Verb" $ do
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
type CaptureApi = Capture "legs" Integer :> Get '[JSON] Animal type CaptureApi = Capture "legs" Integer :> Get '[JSON] Animal
:<|> "ears" :> Capture' '[Lenient] "ears" Integer :> Get '[JSON] Animal
:<|> "eyes" :> Capture' '[Strict] "eyes" Integer :> Get '[JSON] Animal
captureApi :: Proxy CaptureApi captureApi :: Proxy CaptureApi
captureApi = Proxy captureApi = Proxy
captureServer :: Integer -> Handler Animal
captureServer legs = case legs of captureServer :: Server CaptureApi
captureServer = getLegs :<|> getEars :<|> getEyes
where getLegs :: Integer -> Handler Animal
getLegs legs = case legs of
4 -> return jerry 4 -> return jerry
2 -> return tweety 2 -> return tweety
_ -> throwError err404 _ -> throwError err404
getEars :: Either String Integer -> Handler Animal
getEars (Left e) = return chimera -- ignore integer parse error, return weird animal
getEars (Right 2) = return jerry
getEars (Right _) = throwError err404
getEyes :: Integer -> Handler Animal
getEyes 2 = return jerry
getEyes _ = throwError err404
captureSpec :: Spec captureSpec :: Spec
captureSpec = do captureSpec = do
describe "Servant.API.Capture" $ do describe "Servant.API.Capture" $ do
@ -224,6 +238,17 @@ captureSpec = do
it "returns 400 if the decoding fails" $ do it "returns 400 if the decoding fails" $ do
get "/notAnInt" `shouldRespondWith` 400 get "/notAnInt" `shouldRespondWith` 400
it "returns an animal if eyes or ears are 2" $ do
get "/ears/2" `shouldRespondWith` 200
get "/eyes/2" `shouldRespondWith` 200
it "returns a weird animal on Lenient Capture" $ do
response <- get "/ears/bla"
liftIO $ decode' (simpleBody response) `shouldBe` Just chimera
it "returns 400 if parsing integer fails on Strict Capture" $ do
get "/eyes/bla" `shouldRespondWith` 400
with (return (serve with (return (serve
(Proxy :: Proxy (Capture "captured" String :> Raw)) (Proxy :: Proxy (Capture "captured" String :> Raw))
(\ "captured" -> Tagged $ \request_ respond -> (\ "captured" -> Tagged $ \request_ respond ->
@ -780,6 +805,10 @@ jerry = Animal "Mouse" 4
tweety :: Animal tweety :: Animal
tweety = Animal "Bird" 2 tweety = Animal "Bird" 2
-- weird animal with non-integer amount of ears
chimera :: Animal
chimera = Animal "Chimera" (-1)
beholder :: Animal beholder :: Animal
beholder = Animal "Beholder" 0 beholder = Animal "Beholder" 0
-- }}} -- }}}

View File

@ -49,6 +49,7 @@ type ComprehensiveAPIWithoutStreamingOrRaw' endpoint =
GET GET
:<|> "get-int" :> Get '[JSON] Int :<|> "get-int" :> Get '[JSON] Int
:<|> "capture" :> Capture' '[Description "example description"] "foo" Int :> GET :<|> "capture" :> Capture' '[Description "example description"] "foo" Int :> GET
:<|> "capture-lenient" :> Capture' '[Lenient] "foo" Int :> GET
:<|> "header" :> Header "foo" Int :> GET :<|> "header" :> Header "foo" Int :> GET
:<|> "header-lenient" :> Header' '[Required, Lenient] "bar" Int :> GET :<|> "header-lenient" :> Header' '[Required, Lenient] "bar" Int :> GET
:<|> "http-version" :> HttpVersion :> GET :<|> "http-version" :> HttpVersion :> GET