2015-10-12 19:23:13 +02:00
|
|
|
{-# LANGUAGE CPP #-}
|
2015-10-12 19:14:42 +02:00
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE DeriveGeneric #-}
|
2016-01-19 00:19:51 +01:00
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
2015-09-15 11:37:17 +02:00
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
2015-10-12 19:14:42 +02:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2016-01-08 17:43:10 +01:00
|
|
|
{-# LANGUAGE PolyKinds #-}
|
2015-10-12 19:14:42 +02:00
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
2016-01-08 17:43:10 +01:00
|
|
|
{-# LANGUAGE TypeFamilies #-}
|
2016-01-19 00:19:51 +01:00
|
|
|
{-# LANGUAGE TypeOperators #-}
|
2015-10-12 19:14:42 +02:00
|
|
|
{-# LANGUAGE TypeSynonymInstances #-}
|
2017-06-19 17:58:25 +02:00
|
|
|
#if __GLASGOW_HASKELL__ >= 800
|
|
|
|
{-# OPTIONS_GHC -freduction-depth=100 #-}
|
|
|
|
#else
|
2017-06-19 13:59:26 +02:00
|
|
|
{-# OPTIONS_GHC -fcontext-stack=100 #-}
|
2017-06-19 17:58:25 +02:00
|
|
|
#endif
|
2014-12-10 16:10:57 +01:00
|
|
|
|
|
|
|
module Servant.ServerSpec where
|
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
import Control.Monad (forM_, when, unless)
|
2017-01-16 10:44:25 +01:00
|
|
|
import Control.Monad.Error.Class (MonadError (..))
|
2015-03-12 18:29:57 +01:00
|
|
|
import Data.Aeson (FromJSON, ToJSON, decode', encode)
|
2016-04-06 09:24:30 +02:00
|
|
|
import qualified Data.ByteString.Base64 as Base64
|
2015-03-12 18:29:57 +01:00
|
|
|
import Data.Char (toUpper)
|
2016-04-06 09:24:30 +02:00
|
|
|
import Data.Monoid
|
2015-03-12 18:29:57 +01:00
|
|
|
import Data.Proxy (Proxy (Proxy))
|
|
|
|
import Data.String (fromString)
|
|
|
|
import Data.String.Conversions (cs)
|
2015-04-06 16:12:28 +02:00
|
|
|
import qualified Data.Text as T
|
2015-03-12 18:29:57 +01:00
|
|
|
import GHC.Generics (Generic)
|
2016-01-08 17:43:10 +01:00
|
|
|
import Network.HTTP.Types (Status (..), hAccept, hContentType,
|
|
|
|
methodDelete, methodGet,
|
|
|
|
methodHead, methodPatch,
|
|
|
|
methodPost, methodPut, ok200,
|
2017-10-23 07:04:28 +02:00
|
|
|
#if MIN_VERSION_http_types(0,10,0)
|
|
|
|
imATeapot418,
|
|
|
|
#else
|
2016-04-06 05:16:18 +02:00
|
|
|
imATeaPot418,
|
2017-10-23 07:04:28 +02:00
|
|
|
#endif
|
2016-01-08 17:43:10 +01:00
|
|
|
parseQuery)
|
2016-02-17 21:21:57 +01:00
|
|
|
import Network.Wai (Application, Request, requestHeaders, pathInfo,
|
2015-03-12 18:29:57 +01:00
|
|
|
queryString, rawQueryString,
|
2016-04-07 13:45:15 +02:00
|
|
|
responseLBS)
|
2015-03-12 18:29:57 +01:00
|
|
|
import Network.Wai.Test (defaultRequest, request,
|
2016-01-08 17:43:10 +01:00
|
|
|
runSession, simpleBody,
|
|
|
|
simpleHeaders, simpleStatus)
|
2016-02-17 21:21:57 +01:00
|
|
|
import Servant.API ((:<|>) (..), (:>), AuthProtect,
|
|
|
|
BasicAuth, BasicAuthData(BasicAuthData),
|
2016-05-26 20:10:15 +02:00
|
|
|
Capture, CaptureAll, Delete, Get, Header (..),
|
2016-01-08 17:43:10 +01:00
|
|
|
Headers, HttpVersion,
|
|
|
|
IsSecure (..), JSON,
|
|
|
|
NoContent (..), Patch, PlainText,
|
2017-05-16 12:18:57 +02:00
|
|
|
Post, Put, EmptyAPI,
|
2015-10-08 22:40:46 +02:00
|
|
|
QueryFlag, QueryParam, QueryParams,
|
2016-01-08 17:43:10 +01:00
|
|
|
Raw, RemoteHost, ReqBody,
|
|
|
|
StdMethod (..), Verb, addHeader)
|
2016-01-16 19:17:46 +01:00
|
|
|
import Servant.API.Internal.Test.ComprehensiveAPI
|
2015-12-02 21:48:12 +01:00
|
|
|
import Servant.Server (Server, Handler, Tagged (..), err401, err403,
|
2016-04-07 23:34:23 +02:00
|
|
|
err404, serve, serveWithContext,
|
2017-05-16 17:59:41 +02:00
|
|
|
Context((:.), EmptyContext), emptyServer)
|
2016-01-08 17:43:10 +01:00
|
|
|
import Test.Hspec (Spec, context, describe, it,
|
|
|
|
shouldBe, shouldContain)
|
2016-02-17 19:56:15 +01:00
|
|
|
import qualified Test.Hspec.Wai as THW
|
2015-10-13 20:29:14 +02:00
|
|
|
import Test.Hspec.Wai (get, liftIO, matchHeaders,
|
2016-02-17 19:56:15 +01:00
|
|
|
matchStatus, shouldRespondWith,
|
|
|
|
with, (<:>))
|
2016-01-08 17:43:10 +01:00
|
|
|
|
2016-02-17 19:56:15 +01:00
|
|
|
import Servant.Server.Internal.BasicAuth (BasicAuthCheck(BasicAuthCheck),
|
|
|
|
BasicAuthResult(Authorized,Unauthorized))
|
2016-03-06 22:23:55 +01:00
|
|
|
import Servant.Server.Experimental.Auth
|
2016-02-17 21:21:57 +01:00
|
|
|
(AuthHandler, AuthServerData,
|
|
|
|
mkAuthHandler)
|
2016-02-28 23:23:32 +01:00
|
|
|
import Servant.Server.Internal.Context
|
2016-03-08 23:28:27 +01:00
|
|
|
(NamedContext(..))
|
2014-12-10 16:10:57 +01:00
|
|
|
|
2017-10-23 07:04:28 +02:00
|
|
|
#if !MIN_VERSION_http_types(0,10,0)
|
|
|
|
imATeapot418 :: Status
|
|
|
|
imATeapot418 = imATeaPot418
|
|
|
|
#endif
|
|
|
|
|
2016-01-16 19:17:46 +01:00
|
|
|
-- * comprehensive api test
|
|
|
|
|
2016-01-18 19:55:14 +01:00
|
|
|
-- This declaration simply checks that all instances are in place.
|
2016-02-28 23:23:32 +01:00
|
|
|
_ = serveWithContext comprehensiveAPI comprehensiveApiContext
|
2016-01-18 21:27:19 +01:00
|
|
|
|
2016-02-28 23:23:32 +01:00
|
|
|
comprehensiveApiContext :: Context '[NamedContext "foo" '[]]
|
|
|
|
comprehensiveApiContext = NamedContext EmptyContext :. EmptyContext
|
2014-12-10 16:10:57 +01:00
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
-- * Specs
|
2014-12-10 16:10:57 +01:00
|
|
|
|
|
|
|
spec :: Spec
|
|
|
|
spec = do
|
2016-01-08 17:43:10 +01:00
|
|
|
verbSpec
|
2014-12-10 16:10:57 +01:00
|
|
|
captureSpec
|
|
|
|
queryParamSpec
|
2016-01-08 17:43:10 +01:00
|
|
|
reqBodySpec
|
2015-02-24 14:48:17 +01:00
|
|
|
headerSpec
|
2014-12-10 16:10:57 +01:00
|
|
|
rawSpec
|
2016-01-08 17:43:10 +01:00
|
|
|
alternativeSpec
|
2015-04-13 15:13:55 +02:00
|
|
|
responseHeadersSpec
|
2016-01-08 17:43:10 +01:00
|
|
|
miscCombinatorSpec
|
2016-02-17 19:56:15 +01:00
|
|
|
basicAuthSpec
|
2016-02-17 21:21:57 +01:00
|
|
|
genAuthSpec
|
2016-01-08 17:43:10 +01:00
|
|
|
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
-- * verbSpec {{{
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
type VerbApi method status
|
|
|
|
= Verb method status '[JSON] Person
|
|
|
|
:<|> "noContent" :> Verb method status '[JSON] NoContent
|
|
|
|
:<|> "header" :> Verb method status '[JSON] (Headers '[Header "H" Int] Person)
|
|
|
|
:<|> "headerNC" :> Verb method status '[JSON] (Headers '[Header "H" Int] NoContent)
|
2016-04-12 10:35:07 +02:00
|
|
|
:<|> "accept" :> ( Verb method status '[JSON] Person
|
|
|
|
:<|> Verb method status '[PlainText] String
|
|
|
|
)
|
2016-01-08 17:43:10 +01:00
|
|
|
|
|
|
|
verbSpec :: Spec
|
|
|
|
verbSpec = describe "Servant.API.Verb" $ do
|
|
|
|
let server :: Server (VerbApi method status)
|
|
|
|
server = return alice
|
|
|
|
:<|> return NoContent
|
|
|
|
:<|> return (addHeader 5 alice)
|
|
|
|
:<|> return (addHeader 10 NoContent)
|
2016-04-12 10:35:07 +02:00
|
|
|
:<|> (return alice :<|> return "B")
|
2016-01-08 17:43:10 +01:00
|
|
|
get200 = Proxy :: Proxy (VerbApi 'GET 200)
|
|
|
|
post210 = Proxy :: Proxy (VerbApi 'POST 210)
|
|
|
|
put203 = Proxy :: Proxy (VerbApi 'PUT 203)
|
|
|
|
delete280 = Proxy :: Proxy (VerbApi 'DELETE 280)
|
|
|
|
patch214 = Proxy :: Proxy (VerbApi 'PATCH 214)
|
|
|
|
wrongMethod m = if m == methodPatch then methodPost else methodPatch
|
|
|
|
test desc api method (status :: Int) = context desc $
|
|
|
|
|
2016-02-18 16:36:24 +01:00
|
|
|
with (return $ serve api server) $ do
|
2016-01-08 17:43:10 +01:00
|
|
|
|
|
|
|
-- HEAD and 214/215 need not return bodies
|
|
|
|
unless (status `elem` [214, 215] || method == methodHead) $
|
|
|
|
it "returns the person" $ do
|
2016-02-17 19:56:15 +01:00
|
|
|
response <- THW.request method "/" [] ""
|
2016-01-08 17:43:10 +01:00
|
|
|
liftIO $ statusCode (simpleStatus response) `shouldBe` status
|
|
|
|
liftIO $ decode' (simpleBody response) `shouldBe` Just alice
|
|
|
|
|
|
|
|
it "returns no content on NoContent" $ do
|
2016-02-17 19:56:15 +01:00
|
|
|
response <- THW.request method "/noContent" [] ""
|
2016-01-08 17:43:10 +01:00
|
|
|
liftIO $ statusCode (simpleStatus response) `shouldBe` status
|
|
|
|
liftIO $ simpleBody response `shouldBe` ""
|
|
|
|
|
|
|
|
-- HEAD should not return body
|
|
|
|
when (method == methodHead) $
|
|
|
|
it "HEAD returns no content body" $ do
|
2016-02-17 19:56:15 +01:00
|
|
|
response <- THW.request method "/" [] ""
|
2016-01-08 17:43:10 +01:00
|
|
|
liftIO $ simpleBody response `shouldBe` ""
|
|
|
|
|
|
|
|
it "throws 405 on wrong method " $ do
|
2016-02-17 19:56:15 +01:00
|
|
|
THW.request (wrongMethod method) "/" [] ""
|
2016-01-08 17:43:10 +01:00
|
|
|
`shouldRespondWith` 405
|
|
|
|
|
|
|
|
it "returns headers" $ do
|
2016-02-17 19:56:15 +01:00
|
|
|
response1 <- THW.request method "/header" [] ""
|
2016-01-08 17:43:10 +01:00
|
|
|
liftIO $ statusCode (simpleStatus response1) `shouldBe` status
|
|
|
|
liftIO $ simpleHeaders response1 `shouldContain` [("H", "5")]
|
|
|
|
|
2016-02-17 19:56:15 +01:00
|
|
|
response2 <- THW.request method "/header" [] ""
|
2016-01-08 17:43:10 +01:00
|
|
|
liftIO $ statusCode (simpleStatus response2) `shouldBe` status
|
|
|
|
liftIO $ simpleHeaders response2 `shouldContain` [("H", "5")]
|
|
|
|
|
|
|
|
it "handles trailing '/' gracefully" $ do
|
2016-02-17 19:56:15 +01:00
|
|
|
response <- THW.request method "/headerNC/" [] ""
|
2016-01-08 17:43:10 +01:00
|
|
|
liftIO $ statusCode (simpleStatus response) `shouldBe` status
|
|
|
|
|
|
|
|
it "returns 406 if the Accept header is not supported" $ do
|
2016-02-17 19:56:15 +01:00
|
|
|
THW.request method "" [(hAccept, "crazy/mime")] ""
|
2016-01-08 17:43:10 +01:00
|
|
|
`shouldRespondWith` 406
|
|
|
|
|
|
|
|
it "responds if the Accept header is supported" $ do
|
2016-02-17 19:56:15 +01:00
|
|
|
response <- THW.request method ""
|
2016-01-08 17:43:10 +01:00
|
|
|
[(hAccept, "application/json")] ""
|
|
|
|
liftIO $ statusCode (simpleStatus response) `shouldBe` status
|
|
|
|
|
2016-04-12 10:35:07 +02:00
|
|
|
unless (status `elem` [214, 215] || method == methodHead) $
|
|
|
|
it "allows modular specification of supported content types" $ do
|
|
|
|
response <- THW.request method "/accept" [(hAccept, "text/plain")] ""
|
|
|
|
liftIO $ statusCode (simpleStatus response) `shouldBe` status
|
|
|
|
liftIO $ simpleBody response `shouldBe` "B"
|
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
it "sets the Content-Type header" $ do
|
2016-02-17 19:56:15 +01:00
|
|
|
response <- THW.request method "" [] ""
|
2016-01-08 17:43:10 +01:00
|
|
|
liftIO $ simpleHeaders response `shouldContain`
|
2017-01-16 11:13:48 +01:00
|
|
|
[("Content-Type", "application/json;charset=utf-8")]
|
2016-01-08 17:43:10 +01:00
|
|
|
|
|
|
|
test "GET 200" get200 methodGet 200
|
|
|
|
test "POST 210" post210 methodPost 210
|
|
|
|
test "PUT 203" put203 methodPut 203
|
|
|
|
test "DELETE 280" delete280 methodDelete 280
|
|
|
|
test "PATCH 214" patch214 methodPatch 214
|
|
|
|
test "GET 200 with HEAD" get200 methodHead 200
|
|
|
|
|
|
|
|
-- }}}
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
-- * captureSpec {{{
|
|
|
|
------------------------------------------------------------------------------
|
2014-12-10 16:10:57 +01:00
|
|
|
|
2015-01-12 15:08:41 +01:00
|
|
|
type CaptureApi = Capture "legs" Integer :> Get '[JSON] Animal
|
2014-12-10 16:10:57 +01:00
|
|
|
captureApi :: Proxy CaptureApi
|
|
|
|
captureApi = Proxy
|
2016-04-07 23:34:23 +02:00
|
|
|
captureServer :: Integer -> Handler Animal
|
2014-12-10 16:10:57 +01:00
|
|
|
captureServer legs = case legs of
|
|
|
|
4 -> return jerry
|
|
|
|
2 -> return tweety
|
2017-01-16 10:44:25 +01:00
|
|
|
_ -> throwError err404
|
2014-12-10 16:10:57 +01:00
|
|
|
|
|
|
|
captureSpec :: Spec
|
|
|
|
captureSpec = do
|
|
|
|
describe "Servant.API.Capture" $ do
|
2016-02-18 16:36:24 +01:00
|
|
|
with (return (serve captureApi captureServer)) $ do
|
2015-04-06 16:43:36 +02:00
|
|
|
|
2014-12-10 16:10:57 +01:00
|
|
|
it "can capture parts of the 'pathInfo'" $ do
|
|
|
|
response <- get "/2"
|
2015-04-06 16:43:36 +02:00
|
|
|
liftIO $ decode' (simpleBody response) `shouldBe` Just tweety
|
|
|
|
|
2016-03-23 08:06:38 +01:00
|
|
|
it "returns 400 if the decoding fails" $ do
|
|
|
|
get "/notAnInt" `shouldRespondWith` 400
|
2014-12-10 16:10:57 +01:00
|
|
|
|
|
|
|
with (return (serve
|
|
|
|
(Proxy :: Proxy (Capture "captured" String :> Raw))
|
2015-12-02 21:48:12 +01:00
|
|
|
(\ "captured" -> Tagged $ \request_ respond ->
|
2015-01-06 17:26:37 +01:00
|
|
|
respond $ responseLBS ok200 [] (cs $ show $ pathInfo request_)))) $ do
|
2014-12-10 16:10:57 +01:00
|
|
|
it "strips the captured path snippet from pathInfo" $ do
|
|
|
|
get "/captured/foo" `shouldRespondWith` (fromString (show ["foo" :: String]))
|
|
|
|
|
2016-05-26 20:10:15 +02:00
|
|
|
-- }}}
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
-- * captureAllSpec {{{
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
type CaptureAllApi = CaptureAll "legs" Integer :> Get '[JSON] Animal
|
|
|
|
captureAllApi :: Proxy CaptureAllApi
|
|
|
|
captureAllApi = Proxy
|
|
|
|
captureAllServer :: [Integer] -> Handler Animal
|
|
|
|
captureAllServer legs = case sum legs of
|
|
|
|
4 -> return jerry
|
|
|
|
2 -> return tweety
|
|
|
|
0 -> return beholder
|
2017-01-16 10:44:25 +01:00
|
|
|
_ -> throwError err404
|
2016-05-26 20:10:15 +02:00
|
|
|
|
|
|
|
captureAllSpec :: Spec
|
|
|
|
captureAllSpec = do
|
|
|
|
describe "Servant.API.CaptureAll" $ do
|
|
|
|
with (return (serve captureAllApi captureAllServer)) $ do
|
|
|
|
|
|
|
|
it "can capture a single element of the 'pathInfo'" $ do
|
|
|
|
response <- get "/2"
|
|
|
|
liftIO $ decode' (simpleBody response) `shouldBe` Just tweety
|
|
|
|
|
|
|
|
it "can capture multiple elements of the 'pathInfo'" $ do
|
|
|
|
response <- get "/2/2"
|
|
|
|
liftIO $ decode' (simpleBody response) `shouldBe` Just jerry
|
|
|
|
|
|
|
|
it "can capture arbitrarily many elements of the 'pathInfo'" $ do
|
|
|
|
response <- get "/1/1/0/1/0/1"
|
|
|
|
liftIO $ decode' (simpleBody response) `shouldBe` Just jerry
|
|
|
|
|
|
|
|
it "can capture when there are no elements in 'pathInfo'" $ do
|
|
|
|
response <- get "/"
|
|
|
|
liftIO $ decode' (simpleBody response) `shouldBe` Just beholder
|
|
|
|
|
|
|
|
it "returns 400 if the decoding fails" $ do
|
|
|
|
get "/notAnInt" `shouldRespondWith` 400
|
|
|
|
|
|
|
|
it "returns 400 if the decoding fails, regardless of which element" $ do
|
|
|
|
get "/1/0/0/notAnInt/3/" `shouldRespondWith` 400
|
|
|
|
|
|
|
|
it "returns 400 if the decoding fails, even when it's multiple elements" $ do
|
|
|
|
get "/1/0/0/notAnInt/3/orange/" `shouldRespondWith` 400
|
|
|
|
|
|
|
|
with (return (serve
|
|
|
|
(Proxy :: Proxy (CaptureAll "segments" String :> Raw))
|
2015-12-02 21:48:12 +01:00
|
|
|
(\ _captured -> Tagged $ \request_ respond ->
|
2016-05-26 20:10:15 +02:00
|
|
|
respond $ responseLBS ok200 [] (cs $ show $ pathInfo request_)))) $ do
|
|
|
|
it "consumes everything from pathInfo" $ do
|
|
|
|
get "/captured/foo/bar/baz" `shouldRespondWith` (fromString (show ([] :: [Int])))
|
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
-- }}}
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
-- * queryParamSpec {{{
|
|
|
|
------------------------------------------------------------------------------
|
2014-12-10 16:10:57 +01:00
|
|
|
|
2015-01-12 15:08:41 +01:00
|
|
|
type QueryParamApi = QueryParam "name" String :> Get '[JSON] Person
|
|
|
|
:<|> "a" :> QueryParams "names" String :> Get '[JSON] Person
|
|
|
|
:<|> "b" :> QueryFlag "capitalize" :> Get '[JSON] Person
|
2016-12-12 15:17:06 +01:00
|
|
|
:<|> "param" :> QueryParam "age" Integer :> Get '[JSON] Person
|
|
|
|
:<|> "multiparam" :> QueryParams "ages" Integer :> Get '[JSON] Person
|
2014-12-10 16:10:57 +01:00
|
|
|
|
|
|
|
queryParamApi :: Proxy QueryParamApi
|
|
|
|
queryParamApi = Proxy
|
|
|
|
|
|
|
|
qpServer :: Server QueryParamApi
|
2016-12-12 15:17:06 +01:00
|
|
|
qpServer = queryParamServer :<|> qpNames :<|> qpCapitalize :<|> qpAge :<|> qpAges
|
2014-12-10 16:10:57 +01:00
|
|
|
|
|
|
|
where qpNames (_:name2:_) = return alice { name = name2 }
|
|
|
|
qpNames _ = return alice
|
|
|
|
|
|
|
|
qpCapitalize False = return alice
|
|
|
|
qpCapitalize True = return alice { name = map toUpper (name alice) }
|
|
|
|
|
2016-12-12 15:17:06 +01:00
|
|
|
qpAge Nothing = return alice
|
|
|
|
qpAge (Just age') = return alice{ age = age'}
|
|
|
|
|
|
|
|
qpAges ages = return alice{ age = sum ages}
|
|
|
|
|
2015-01-06 17:26:37 +01:00
|
|
|
queryParamServer (Just name_) = return alice{name = name_}
|
2014-12-10 16:10:57 +01:00
|
|
|
queryParamServer Nothing = return alice
|
|
|
|
|
|
|
|
queryParamSpec :: Spec
|
|
|
|
queryParamSpec = do
|
|
|
|
describe "Servant.API.QueryParam" $ do
|
2016-01-14 23:43:48 +01:00
|
|
|
it "allows retrieving simple GET parameters" $
|
2016-02-18 16:36:24 +01:00
|
|
|
(flip runSession) (serve queryParamApi qpServer) $ do
|
2014-12-10 16:10:57 +01:00
|
|
|
let params1 = "?name=bob"
|
|
|
|
response1 <- Network.Wai.Test.request defaultRequest{
|
|
|
|
rawQueryString = params1,
|
|
|
|
queryString = parseQuery params1
|
|
|
|
}
|
|
|
|
liftIO $ do
|
|
|
|
decode' (simpleBody response1) `shouldBe` Just alice{
|
|
|
|
name = "bob"
|
|
|
|
}
|
|
|
|
|
2016-01-14 23:43:48 +01:00
|
|
|
it "allows retrieving lists in GET parameters" $
|
2016-02-18 16:36:24 +01:00
|
|
|
(flip runSession) (serve queryParamApi qpServer) $ do
|
2014-12-10 16:10:57 +01:00
|
|
|
let params2 = "?names[]=bob&names[]=john"
|
|
|
|
response2 <- Network.Wai.Test.request defaultRequest{
|
|
|
|
rawQueryString = params2,
|
|
|
|
queryString = parseQuery params2,
|
|
|
|
pathInfo = ["a"]
|
|
|
|
}
|
|
|
|
liftIO $
|
|
|
|
decode' (simpleBody response2) `shouldBe` Just alice{
|
|
|
|
name = "john"
|
|
|
|
}
|
|
|
|
|
2016-12-12 15:17:06 +01:00
|
|
|
it "parses a query parameter" $
|
|
|
|
(flip runSession) (serve queryParamApi qpServer) $ do
|
|
|
|
let params = "?age=55"
|
|
|
|
response <- Network.Wai.Test.request defaultRequest{
|
|
|
|
rawQueryString = params,
|
|
|
|
queryString = parseQuery params,
|
|
|
|
pathInfo = ["param"]
|
|
|
|
}
|
|
|
|
liftIO $
|
|
|
|
decode' (simpleBody response) `shouldBe` Just alice{
|
|
|
|
age = 55
|
|
|
|
}
|
|
|
|
|
|
|
|
it "generates an error on query parameter parse failure" $
|
|
|
|
(flip runSession) (serve queryParamApi qpServer) $ do
|
|
|
|
let params = "?age=foo"
|
|
|
|
response <- Network.Wai.Test.request defaultRequest{
|
|
|
|
rawQueryString = params,
|
|
|
|
queryString = parseQuery params,
|
|
|
|
pathInfo = ["param"]
|
|
|
|
}
|
|
|
|
liftIO $ statusCode (simpleStatus response) `shouldBe` 400
|
|
|
|
return ()
|
|
|
|
|
|
|
|
it "parses multiple query parameters" $
|
|
|
|
(flip runSession) (serve queryParamApi qpServer) $ do
|
|
|
|
let params = "?ages=10&ages=22"
|
|
|
|
response <- Network.Wai.Test.request defaultRequest{
|
|
|
|
rawQueryString = params,
|
|
|
|
queryString = parseQuery params,
|
|
|
|
pathInfo = ["multiparam"]
|
|
|
|
}
|
|
|
|
liftIO $
|
|
|
|
decode' (simpleBody response) `shouldBe` Just alice{
|
|
|
|
age = 32
|
|
|
|
}
|
|
|
|
|
|
|
|
it "generates an error on parse failures of multiple parameters" $
|
|
|
|
(flip runSession) (serve queryParamApi qpServer) $ do
|
|
|
|
let params = "?ages=2&ages=foo"
|
|
|
|
response <- Network.Wai.Test.request defaultRequest{
|
|
|
|
rawQueryString = params,
|
|
|
|
queryString = parseQuery params,
|
|
|
|
pathInfo = ["multiparam"]
|
|
|
|
}
|
|
|
|
liftIO $ statusCode (simpleStatus response) `shouldBe` 400
|
|
|
|
return ()
|
|
|
|
|
2015-01-13 20:40:41 +01:00
|
|
|
|
2016-01-14 23:43:48 +01:00
|
|
|
it "allows retrieving value-less GET parameters" $
|
2016-02-18 16:36:24 +01:00
|
|
|
(flip runSession) (serve queryParamApi qpServer) $ do
|
2014-12-10 16:10:57 +01:00
|
|
|
let params3 = "?capitalize"
|
|
|
|
response3 <- Network.Wai.Test.request defaultRequest{
|
|
|
|
rawQueryString = params3,
|
|
|
|
queryString = parseQuery params3,
|
|
|
|
pathInfo = ["b"]
|
|
|
|
}
|
|
|
|
liftIO $
|
|
|
|
decode' (simpleBody response3) `shouldBe` Just alice{
|
|
|
|
name = "ALICE"
|
|
|
|
}
|
|
|
|
|
|
|
|
let params3' = "?capitalize="
|
|
|
|
response3' <- Network.Wai.Test.request defaultRequest{
|
|
|
|
rawQueryString = params3',
|
|
|
|
queryString = parseQuery params3',
|
|
|
|
pathInfo = ["b"]
|
|
|
|
}
|
|
|
|
liftIO $
|
|
|
|
decode' (simpleBody response3') `shouldBe` Just alice{
|
|
|
|
name = "ALICE"
|
|
|
|
}
|
|
|
|
|
2014-12-28 23:07:14 +01:00
|
|
|
let params3'' = "?unknown="
|
2015-09-16 22:07:55 +02:00
|
|
|
response3'' <- Network.Wai.Test.request defaultRequest{
|
2014-12-28 23:07:14 +01:00
|
|
|
rawQueryString = params3'',
|
|
|
|
queryString = parseQuery params3'',
|
|
|
|
pathInfo = ["b"]
|
|
|
|
}
|
|
|
|
liftIO $
|
2015-09-16 22:07:55 +02:00
|
|
|
decode' (simpleBody response3'') `shouldBe` Just alice{
|
2014-12-28 23:07:14 +01:00
|
|
|
name = "Alice"
|
|
|
|
}
|
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
-- }}}
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
-- * reqBodySpec {{{
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
type ReqBodyApi = ReqBody '[JSON] Person :> Post '[JSON] Person
|
|
|
|
:<|> "blah" :> ReqBody '[JSON] Person :> Put '[JSON] Integer
|
2015-01-05 14:27:06 +01:00
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
reqBodyApi :: Proxy ReqBodyApi
|
|
|
|
reqBodyApi = Proxy
|
2015-03-12 18:29:57 +01:00
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
reqBodySpec :: Spec
|
|
|
|
reqBodySpec = describe "Servant.API.ReqBody" $ do
|
2015-03-12 18:29:57 +01:00
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
let server :: Server ReqBodyApi
|
|
|
|
server = return :<|> return . age
|
2016-02-17 19:56:15 +01:00
|
|
|
mkReq method x = THW.request method x
|
2016-01-08 17:43:10 +01:00
|
|
|
[(hContentType, "application/json;charset=utf-8")]
|
2015-03-12 18:29:57 +01:00
|
|
|
|
2016-02-18 16:36:24 +01:00
|
|
|
with (return $ serve reqBodyApi server) $ do
|
2015-03-12 18:29:57 +01:00
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
it "passes the argument to the handler" $ do
|
|
|
|
response <- mkReq methodPost "" (encode alice)
|
|
|
|
liftIO $ decode' (simpleBody response) `shouldBe` Just alice
|
2015-03-12 18:29:57 +01:00
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
it "rejects invalid request bodies with status 400" $ do
|
|
|
|
mkReq methodPut "/blah" "some invalid body" `shouldRespondWith` 400
|
2015-03-12 18:29:57 +01:00
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
it "responds with 415 if the request body media type is unsupported" $ do
|
2016-02-17 19:56:15 +01:00
|
|
|
THW.request methodPost "/"
|
2016-01-08 17:43:10 +01:00
|
|
|
[(hContentType, "application/nonsense")] "" `shouldRespondWith` 415
|
2015-03-12 18:29:57 +01:00
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
-- }}}
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
-- * headerSpec {{{
|
|
|
|
------------------------------------------------------------------------------
|
2015-03-12 18:29:57 +01:00
|
|
|
|
2016-07-08 09:11:34 +02:00
|
|
|
type HeaderApi a = Header "MyHeader" a :> Delete '[JSON] NoContent
|
2015-02-24 14:48:17 +01:00
|
|
|
headerApi :: Proxy (HeaderApi a)
|
|
|
|
headerApi = Proxy
|
|
|
|
|
|
|
|
headerSpec :: Spec
|
|
|
|
headerSpec = describe "Servant.API.Header" $ do
|
|
|
|
|
2016-07-08 09:11:34 +02:00
|
|
|
let expectsInt :: Maybe Int -> Handler NoContent
|
|
|
|
expectsInt (Just x) = do
|
|
|
|
when (x /= 5) $ error "Expected 5"
|
|
|
|
return NoContent
|
2015-02-24 14:48:17 +01:00
|
|
|
expectsInt Nothing = error "Expected an int"
|
|
|
|
|
2016-07-08 09:11:34 +02:00
|
|
|
let expectsString :: Maybe String -> Handler NoContent
|
|
|
|
expectsString (Just x) = do
|
|
|
|
when (x /= "more from you") $ error "Expected more from you"
|
|
|
|
return NoContent
|
2015-02-24 14:48:17 +01:00
|
|
|
expectsString Nothing = error "Expected a string"
|
|
|
|
|
2016-02-18 16:36:24 +01:00
|
|
|
with (return (serve headerApi expectsInt)) $ do
|
2016-03-06 21:16:28 +01:00
|
|
|
let delete' x = THW.request methodDelete x [("MyHeader", "5")]
|
2015-02-24 14:48:17 +01:00
|
|
|
|
|
|
|
it "passes the header to the handler (Int)" $
|
2015-12-27 02:05:36 +01:00
|
|
|
delete' "/" "" `shouldRespondWith` 200
|
2015-02-24 14:48:17 +01:00
|
|
|
|
2016-02-18 16:36:24 +01:00
|
|
|
with (return (serve headerApi expectsString)) $ do
|
2016-03-06 21:16:28 +01:00
|
|
|
let delete' x = THW.request methodDelete x [("MyHeader", "more from you")]
|
2015-02-24 14:48:17 +01:00
|
|
|
|
|
|
|
it "passes the header to the handler (String)" $
|
2015-12-27 02:05:36 +01:00
|
|
|
delete' "/" "" `shouldRespondWith` 200
|
2015-02-24 14:48:17 +01:00
|
|
|
|
2017-04-06 13:59:16 +02:00
|
|
|
with (return (serve headerApi expectsInt)) $ do
|
|
|
|
let delete' x = THW.request methodDelete x [("MyHeader", "not a number")]
|
|
|
|
|
|
|
|
it "checks for parse errors" $
|
|
|
|
delete' "/" "" `shouldRespondWith` 400
|
|
|
|
|
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
-- }}}
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
-- * rawSpec {{{
|
|
|
|
------------------------------------------------------------------------------
|
2014-12-10 16:10:57 +01:00
|
|
|
|
|
|
|
type RawApi = "foo" :> Raw
|
2016-01-08 17:43:10 +01:00
|
|
|
|
2014-12-10 16:10:57 +01:00
|
|
|
rawApi :: Proxy RawApi
|
|
|
|
rawApi = Proxy
|
2016-01-08 17:43:10 +01:00
|
|
|
|
2015-12-02 21:48:12 +01:00
|
|
|
rawApplication :: Show a => (Request -> a) -> Tagged m Application
|
|
|
|
rawApplication f = Tagged $ \request_ respond ->
|
|
|
|
respond $ responseLBS ok200 []
|
|
|
|
(cs $ show $ f request_)
|
2014-12-10 16:10:57 +01:00
|
|
|
|
|
|
|
rawSpec :: Spec
|
|
|
|
rawSpec = do
|
|
|
|
describe "Servant.API.Raw" $ do
|
|
|
|
it "runs applications" $ do
|
2016-02-18 16:36:24 +01:00
|
|
|
(flip runSession) (serve rawApi (rawApplication (const (42 :: Integer)))) $ do
|
2014-12-10 16:10:57 +01:00
|
|
|
response <- Network.Wai.Test.request defaultRequest{
|
|
|
|
pathInfo = ["foo"]
|
|
|
|
}
|
|
|
|
liftIO $ do
|
|
|
|
simpleBody response `shouldBe` "42"
|
|
|
|
|
|
|
|
it "gets the pathInfo modified" $ do
|
2016-02-18 16:36:24 +01:00
|
|
|
(flip runSession) (serve rawApi (rawApplication pathInfo)) $ do
|
2014-12-10 16:10:57 +01:00
|
|
|
response <- Network.Wai.Test.request defaultRequest{
|
|
|
|
pathInfo = ["foo", "bar"]
|
|
|
|
}
|
|
|
|
liftIO $ do
|
|
|
|
simpleBody response `shouldBe` cs (show ["bar" :: String])
|
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
-- }}}
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
-- * alternativeSpec {{{
|
|
|
|
------------------------------------------------------------------------------
|
2014-12-10 16:10:57 +01:00
|
|
|
type AlternativeApi =
|
2015-01-12 15:08:41 +01:00
|
|
|
"foo" :> Get '[JSON] Person
|
|
|
|
:<|> "bar" :> Get '[JSON] Animal
|
2015-04-06 16:12:28 +02:00
|
|
|
:<|> "foo" :> Get '[PlainText] T.Text
|
2015-04-06 16:43:36 +02:00
|
|
|
:<|> "bar" :> Post '[JSON] Animal
|
|
|
|
:<|> "bar" :> Put '[JSON] Animal
|
2016-07-08 09:11:34 +02:00
|
|
|
:<|> "bar" :> Delete '[JSON] NoContent
|
2014-12-10 16:10:57 +01:00
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
alternativeApi :: Proxy AlternativeApi
|
|
|
|
alternativeApi = Proxy
|
|
|
|
|
|
|
|
alternativeServer :: Server AlternativeApi
|
|
|
|
alternativeServer =
|
2014-12-10 16:10:57 +01:00
|
|
|
return alice
|
|
|
|
:<|> return jerry
|
2015-04-06 16:12:28 +02:00
|
|
|
:<|> return "a string"
|
2015-04-06 16:43:36 +02:00
|
|
|
:<|> return jerry
|
|
|
|
:<|> return jerry
|
2016-07-08 09:11:34 +02:00
|
|
|
:<|> return NoContent
|
2014-12-10 16:10:57 +01:00
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
alternativeSpec :: Spec
|
|
|
|
alternativeSpec = do
|
2014-12-10 16:10:57 +01:00
|
|
|
describe "Servant.API.Alternative" $ do
|
2016-02-18 16:36:24 +01:00
|
|
|
with (return $ serve alternativeApi alternativeServer) $ do
|
2015-04-06 16:43:36 +02:00
|
|
|
|
2014-12-10 16:10:57 +01:00
|
|
|
it "unions endpoints" $ do
|
|
|
|
response <- get "/foo"
|
|
|
|
liftIO $ do
|
|
|
|
decode' (simpleBody response) `shouldBe`
|
|
|
|
Just alice
|
2015-01-06 17:26:37 +01:00
|
|
|
response_ <- get "/bar"
|
2014-12-10 16:10:57 +01:00
|
|
|
liftIO $ do
|
2015-01-06 17:26:37 +01:00
|
|
|
decode' (simpleBody response_) `shouldBe`
|
2014-12-10 16:10:57 +01:00
|
|
|
Just jerry
|
2015-04-06 16:43:36 +02:00
|
|
|
|
|
|
|
it "checks all endpoints before returning 415" $ do
|
2015-04-06 16:12:28 +02:00
|
|
|
get "/foo" `shouldRespondWith` 200
|
2015-01-30 01:36:01 +01:00
|
|
|
|
2015-04-06 16:43:36 +02:00
|
|
|
it "returns 404 if the path does not exist" $ do
|
|
|
|
get "/nonexistent" `shouldRespondWith` 404
|
2016-01-08 17:43:10 +01:00
|
|
|
-- }}}
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
-- * responseHeaderSpec {{{
|
|
|
|
------------------------------------------------------------------------------
|
2015-04-13 15:13:55 +02:00
|
|
|
type ResponseHeadersApi =
|
|
|
|
Get '[JSON] (Headers '[Header "H1" Int, Header "H2" String] String)
|
|
|
|
:<|> Post '[JSON] (Headers '[Header "H1" Int, Header "H2" String] String)
|
|
|
|
:<|> Put '[JSON] (Headers '[Header "H1" Int, Header "H2" String] String)
|
|
|
|
:<|> Patch '[JSON] (Headers '[Header "H1" Int, Header "H2" String] String)
|
|
|
|
|
|
|
|
|
|
|
|
responseHeadersServer :: Server ResponseHeadersApi
|
|
|
|
responseHeadersServer = let h = return $ addHeader 5 $ addHeader "kilroy" "hi"
|
|
|
|
in h :<|> h :<|> h :<|> h
|
|
|
|
|
|
|
|
|
|
|
|
responseHeadersSpec :: Spec
|
|
|
|
responseHeadersSpec = describe "ResponseHeaders" $ do
|
2016-02-18 16:36:24 +01:00
|
|
|
with (return $ serve (Proxy :: Proxy ResponseHeadersApi) responseHeadersServer) $ do
|
2015-04-13 15:13:55 +02:00
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
let methods = [methodGet, methodPost, methodPut, methodPatch]
|
2015-04-13 15:13:55 +02:00
|
|
|
|
|
|
|
it "includes the headers in the response" $
|
2016-01-08 17:43:10 +01:00
|
|
|
forM_ methods $ \method ->
|
2016-02-17 19:56:15 +01:00
|
|
|
THW.request method "/" [] ""
|
2015-04-13 15:13:55 +02:00
|
|
|
`shouldRespondWith` "\"hi\""{ matchHeaders = ["H1" <:> "5", "H2" <:> "kilroy"]
|
2016-01-08 17:43:10 +01:00
|
|
|
, matchStatus = 200
|
2015-04-13 15:13:55 +02:00
|
|
|
}
|
|
|
|
|
|
|
|
it "responds with not found for non-existent endpoints" $
|
2016-01-08 17:43:10 +01:00
|
|
|
forM_ methods $ \method ->
|
2016-02-17 19:56:15 +01:00
|
|
|
THW.request method "blahblah" [] ""
|
2015-04-13 15:13:55 +02:00
|
|
|
`shouldRespondWith` 404
|
|
|
|
|
2015-09-10 08:49:19 +02:00
|
|
|
it "returns 406 if the Accept header is not supported" $
|
2016-01-08 17:43:10 +01:00
|
|
|
forM_ methods $ \method ->
|
2016-02-17 19:56:15 +01:00
|
|
|
THW.request method "" [(hAccept, "crazy/mime")] ""
|
2015-09-10 08:49:19 +02:00
|
|
|
`shouldRespondWith` 406
|
2015-04-13 15:13:55 +02:00
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
-- }}}
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
-- * miscCombinatorSpec {{{
|
|
|
|
------------------------------------------------------------------------------
|
2015-06-23 10:34:20 +02:00
|
|
|
type MiscCombinatorsAPI
|
|
|
|
= "version" :> HttpVersion :> Get '[JSON] String
|
|
|
|
:<|> "secure" :> IsSecure :> Get '[JSON] String
|
|
|
|
:<|> "host" :> RemoteHost :> Get '[JSON] String
|
2017-05-16 12:18:57 +02:00
|
|
|
:<|> "empty" :> EmptyAPI
|
2015-06-23 10:34:20 +02:00
|
|
|
|
|
|
|
miscApi :: Proxy MiscCombinatorsAPI
|
|
|
|
miscApi = Proxy
|
|
|
|
|
|
|
|
miscServ :: Server MiscCombinatorsAPI
|
|
|
|
miscServ = versionHandler
|
|
|
|
:<|> secureHandler
|
|
|
|
:<|> hostHandler
|
2017-05-16 17:59:41 +02:00
|
|
|
:<|> emptyServer
|
2015-06-23 10:34:20 +02:00
|
|
|
|
|
|
|
where versionHandler = return . show
|
|
|
|
secureHandler Secure = return "secure"
|
|
|
|
secureHandler NotSecure = return "not secure"
|
|
|
|
hostHandler = return . show
|
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
miscCombinatorSpec :: Spec
|
2016-02-18 16:36:24 +01:00
|
|
|
miscCombinatorSpec = with (return $ serve miscApi miscServ) $
|
2015-06-23 10:34:20 +02:00
|
|
|
describe "Misc. combinators for request inspection" $ do
|
|
|
|
it "Successfully gets the HTTP version specified in the request" $
|
|
|
|
go "/version" "\"HTTP/1.0\""
|
|
|
|
|
|
|
|
it "Checks that hspec-wai uses HTTP, not HTTPS" $
|
|
|
|
go "/secure" "\"not secure\""
|
|
|
|
|
|
|
|
it "Checks that hspec-wai issues request from 0.0.0.0" $
|
|
|
|
go "/host" "\"0.0.0.0:0\""
|
|
|
|
|
2017-05-16 12:18:57 +02:00
|
|
|
it "Doesn't serve anything from the empty API" $
|
|
|
|
Test.Hspec.Wai.get "empty" `shouldRespondWith` 404
|
|
|
|
|
2015-06-23 10:34:20 +02:00
|
|
|
where go path res = Test.Hspec.Wai.get path `shouldRespondWith` res
|
2016-02-17 19:56:15 +01:00
|
|
|
|
|
|
|
-- }}}
|
|
|
|
------------------------------------------------------------------------------
|
2016-02-17 21:21:57 +01:00
|
|
|
-- * Basic Authentication {{{
|
2016-02-17 19:56:15 +01:00
|
|
|
------------------------------------------------------------------------------
|
|
|
|
|
2016-04-06 05:16:18 +02:00
|
|
|
type BasicAuthAPI =
|
|
|
|
BasicAuth "foo" () :> "basic" :> Get '[JSON] Animal
|
|
|
|
:<|> Raw
|
2016-02-17 19:56:15 +01:00
|
|
|
|
|
|
|
basicAuthApi :: Proxy BasicAuthAPI
|
|
|
|
basicAuthApi = Proxy
|
2016-04-06 04:59:49 +02:00
|
|
|
|
2016-02-17 19:56:15 +01:00
|
|
|
basicAuthServer :: Server BasicAuthAPI
|
2016-04-06 05:16:18 +02:00
|
|
|
basicAuthServer =
|
|
|
|
const (return jerry) :<|>
|
2017-10-23 07:04:28 +02:00
|
|
|
(Tagged $ \ _ respond -> respond $ responseLBS imATeapot418 [] "")
|
2016-02-17 19:56:15 +01:00
|
|
|
|
|
|
|
basicAuthContext :: Context '[ BasicAuthCheck () ]
|
|
|
|
basicAuthContext =
|
2016-04-06 04:59:49 +02:00
|
|
|
let basicHandler = BasicAuthCheck $ \(BasicAuthData usr pass) ->
|
2016-02-17 19:56:15 +01:00
|
|
|
if usr == "servant" && pass == "server"
|
2016-04-06 04:59:49 +02:00
|
|
|
then return (Authorized ())
|
|
|
|
else return Unauthorized
|
2016-02-17 19:56:15 +01:00
|
|
|
in basicHandler :. EmptyContext
|
|
|
|
|
|
|
|
basicAuthSpec :: Spec
|
|
|
|
basicAuthSpec = do
|
|
|
|
describe "Servant.API.BasicAuth" $ do
|
|
|
|
with (return (serveWithContext basicAuthApi basicAuthContext basicAuthServer)) $ do
|
|
|
|
|
|
|
|
context "Basic Authentication" $ do
|
2016-04-06 09:24:30 +02:00
|
|
|
let basicAuthHeaders user password =
|
|
|
|
[("Authorization", "Basic " <> Base64.encode (user <> ":" <> password))]
|
2016-04-06 05:16:18 +02:00
|
|
|
it "returns 401 when no credentials given" $ do
|
2016-02-17 19:56:15 +01:00
|
|
|
get "/basic" `shouldRespondWith` 401
|
2016-04-06 04:59:49 +02:00
|
|
|
|
2016-04-06 05:16:18 +02:00
|
|
|
it "returns 403 when invalid credentials given" $ do
|
2016-04-06 09:24:30 +02:00
|
|
|
THW.request methodGet "/basic" (basicAuthHeaders "servant" "wrong") ""
|
2016-04-06 05:16:18 +02:00
|
|
|
`shouldRespondWith` 403
|
|
|
|
|
2016-02-17 19:56:15 +01:00
|
|
|
it "returns 200 with the right password" $ do
|
2016-04-06 09:24:30 +02:00
|
|
|
THW.request methodGet "/basic" (basicAuthHeaders "servant" "server") ""
|
2016-04-06 04:59:49 +02:00
|
|
|
`shouldRespondWith` 200
|
2016-02-17 19:56:15 +01:00
|
|
|
|
2016-04-06 05:16:18 +02:00
|
|
|
it "plays nice with subsequent Raw endpoints" $ do
|
|
|
|
get "/foo" `shouldRespondWith` 418
|
|
|
|
|
2016-02-17 21:21:57 +01:00
|
|
|
-- }}}
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
-- * General Authentication {{{
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
type GenAuthAPI = AuthProtect "auth" :> "auth" :> Get '[JSON] Animal
|
2016-04-06 13:45:44 +02:00
|
|
|
:<|> Raw
|
2016-04-06 04:59:49 +02:00
|
|
|
|
2016-04-06 13:45:44 +02:00
|
|
|
genAuthApi :: Proxy GenAuthAPI
|
|
|
|
genAuthApi = Proxy
|
2016-04-06 04:59:49 +02:00
|
|
|
|
2016-04-06 13:45:44 +02:00
|
|
|
genAuthServer :: Server GenAuthAPI
|
|
|
|
genAuthServer = const (return tweety)
|
2017-10-23 07:04:28 +02:00
|
|
|
:<|> (Tagged $ \ _ respond -> respond $ responseLBS imATeapot418 [] "")
|
2016-02-17 21:21:57 +01:00
|
|
|
|
|
|
|
type instance AuthServerData (AuthProtect "auth") = ()
|
|
|
|
|
2016-04-06 04:59:49 +02:00
|
|
|
genAuthContext :: Context '[AuthHandler Request ()]
|
2016-02-17 21:21:57 +01:00
|
|
|
genAuthContext =
|
2016-04-07 12:04:36 +02:00
|
|
|
let authHandler = \req -> case lookup "Auth" (requestHeaders req) of
|
|
|
|
Just "secret" -> return ()
|
2017-01-16 10:44:25 +01:00
|
|
|
Just _ -> throwError err403
|
|
|
|
Nothing -> throwError err401
|
2016-02-17 21:21:57 +01:00
|
|
|
in mkAuthHandler authHandler :. EmptyContext
|
|
|
|
|
|
|
|
genAuthSpec :: Spec
|
|
|
|
genAuthSpec = do
|
|
|
|
describe "Servant.API.Auth" $ do
|
2016-04-06 13:45:44 +02:00
|
|
|
with (return (serveWithContext genAuthApi genAuthContext genAuthServer)) $ do
|
2016-02-17 21:21:57 +01:00
|
|
|
|
|
|
|
context "Custom Auth Protection" $ do
|
|
|
|
it "returns 401 when missing headers" $ do
|
|
|
|
get "/auth" `shouldRespondWith` 401
|
2016-04-06 04:59:49 +02:00
|
|
|
|
2016-04-07 12:04:36 +02:00
|
|
|
it "returns 403 on wrong passwords" $ do
|
|
|
|
THW.request methodGet "/auth" [("Auth","wrong")] "" `shouldRespondWith` 403
|
|
|
|
|
2016-02-17 21:21:57 +01:00
|
|
|
it "returns 200 with the right header" $ do
|
|
|
|
THW.request methodGet "/auth" [("Auth","secret")] "" `shouldRespondWith` 200
|
|
|
|
|
2016-04-06 13:45:44 +02:00
|
|
|
it "plays nice with subsequent Raw endpoints" $ do
|
|
|
|
get "/foo" `shouldRespondWith` 418
|
|
|
|
|
2016-01-08 17:43:10 +01:00
|
|
|
-- }}}
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
-- * Test data types {{{
|
|
|
|
------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
data Person = Person {
|
|
|
|
name :: String,
|
|
|
|
age :: Integer
|
|
|
|
}
|
|
|
|
deriving (Eq, Show, Generic)
|
|
|
|
|
|
|
|
instance ToJSON Person
|
|
|
|
instance FromJSON Person
|
|
|
|
|
|
|
|
alice :: Person
|
|
|
|
alice = Person "Alice" 42
|
|
|
|
|
|
|
|
data Animal = Animal {
|
|
|
|
species :: String,
|
|
|
|
numberOfLegs :: Integer
|
|
|
|
}
|
|
|
|
deriving (Eq, Show, Generic)
|
|
|
|
|
|
|
|
instance ToJSON Animal
|
|
|
|
instance FromJSON Animal
|
|
|
|
|
|
|
|
jerry :: Animal
|
|
|
|
jerry = Animal "Mouse" 4
|
|
|
|
|
|
|
|
tweety :: Animal
|
|
|
|
tweety = Animal "Bird" 2
|
2016-05-26 20:10:15 +02:00
|
|
|
|
|
|
|
beholder :: Animal
|
|
|
|
beholder = Animal "Beholder" 0
|
2016-01-08 17:43:10 +01:00
|
|
|
-- }}}
|