test suite: Post
This commit is contained in:
parent
13664a218c
commit
d0782db08b
2 changed files with 26 additions and 4 deletions
|
@ -8,7 +8,6 @@ module Servant.API.RQBody where
|
|||
import Control.Applicative
|
||||
import Data.Aeson
|
||||
import Data.Proxy
|
||||
import Data.Text
|
||||
import Network.Wai
|
||||
import Servant.API.Sub
|
||||
import Servant.Client
|
||||
|
|
|
@ -1,7 +1,9 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
|
||||
module Servant.ServerSpec where
|
||||
|
||||
|
@ -14,6 +16,9 @@ import Test.Hspec
|
|||
import Test.Hspec.Wai
|
||||
|
||||
import Servant.API.Get
|
||||
import Servant.API.Post
|
||||
import Servant.API.RQBody
|
||||
import Servant.API.Sub
|
||||
import Servant.Server
|
||||
|
||||
|
||||
|
@ -27,23 +32,41 @@ instance ToJSON Person
|
|||
instance FromJSON Person
|
||||
|
||||
alice :: Person
|
||||
alice = Person "Alice" 103
|
||||
alice = Person "Alice" 42
|
||||
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
getSpec
|
||||
postSpec
|
||||
|
||||
|
||||
type GetApi = Get Person
|
||||
getApi :: Proxy GetApi
|
||||
getApi = Proxy
|
||||
|
||||
getSpec = do
|
||||
getSpec :: Spec = do
|
||||
describe "Servant.API.Get" $ do
|
||||
with (return (serve getApi (return alice))) $ do
|
||||
it "serves a Person" $ do
|
||||
it "allows to GET a Person" $ do
|
||||
response <- get "/"
|
||||
return response `shouldRespondWith` 200
|
||||
liftIO $ do
|
||||
decode' (simpleBody response) `shouldBe` Just alice
|
||||
|
||||
it "throws 404 on POSTs" $ do
|
||||
post "/" "" `shouldRespondWith` 404
|
||||
|
||||
|
||||
type PostApi = RQBody Person :> (Post Integer)
|
||||
postApi :: Proxy PostApi
|
||||
postApi = Proxy
|
||||
|
||||
postSpec :: Spec
|
||||
postSpec = do
|
||||
describe "Servant.API.Post and .RQBody" $ do
|
||||
with (return (serve postApi (return . age))) $ do
|
||||
it "allows to POST a Person" $ do
|
||||
post "/" (encode alice) `shouldRespondWith` "42"{
|
||||
matchStatus = 201
|
||||
}
|
||||
|
|
Loading…
Reference in a new issue