Pay down some coverage debt

This commit is contained in:
Julian K. Arni 2015-02-24 14:48:17 +01:00
parent 81c3589624
commit b96a2d214d

View file

@ -8,6 +8,7 @@
module Servant.ServerSpec where module Servant.ServerSpec where
import Control.Monad (when)
import Control.Monad.Trans.Either (EitherT, left) import Control.Monad.Trans.Either (EitherT, left)
import Data.Aeson (ToJSON, FromJSON, encode, decode') import Data.Aeson (ToJSON, FromJSON, encode, decode')
import Data.Char (toUpper) import Data.Char (toUpper)
@ -16,7 +17,8 @@ import Data.Proxy (Proxy(Proxy))
import Data.String (fromString) import Data.String (fromString)
import Data.String.Conversions (cs) import Data.String.Conversions (cs)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Network.HTTP.Types (parseQuery, ok200, status409, methodPost, hContentType) import Network.HTTP.Types ( parseQuery, ok200, status409, methodPost
, methodDelete, hContentType)
import Network.Wai ( Application, Request, responseLBS, pathInfo import Network.Wai ( Application, Request, responseLBS, pathInfo
, queryString, rawQueryString ) , queryString, rawQueryString )
import Network.Wai.Test (runSession, defaultRequest, simpleBody, request) import Network.Wai.Test (runSession, defaultRequest, simpleBody, request)
@ -24,16 +26,9 @@ import Test.Hspec (Spec, describe, it, shouldBe)
import Test.Hspec.Wai ( liftIO, with, get, post, shouldRespondWith import Test.Hspec.Wai ( liftIO, with, get, post, shouldRespondWith
, matchStatus, request ) , matchStatus, request )
import Servant.API (JSON) import Servant.API (JSON, Capture, Get, ReqBody, Post, QueryParam
import Servant.API.Capture (Capture) , QueryParams, QueryFlag, MatrixParam, MatrixParams
import Servant.API.Get (Get) , MatrixFlag, Raw, (:>), (:<|>)(..), Header, Delete )
import Servant.API.ReqBody (ReqBody)
import Servant.API.Post (Post)
import Servant.API.QueryParam (QueryParam, QueryParams, QueryFlag)
import Servant.API.MatrixParam (MatrixParam, MatrixParams, MatrixFlag)
import Servant.API.Raw (Raw)
import Servant.API.Sub ((:>))
import Servant.API.Alternative ((:<|>)((:<|>)))
import Servant.Server (Server, serve) import Servant.Server (Server, serve)
import Servant.Server.Internal (RouteMismatch(..)) import Servant.Server.Internal (RouteMismatch(..))
@ -77,6 +72,7 @@ spec = do
queryParamSpec queryParamSpec
matrixParamSpec matrixParamSpec
postSpec postSpec
headerSpec
rawSpec rawSpec
unionSpec unionSpec
errorsSpec errorsSpec
@ -328,6 +324,33 @@ postSpec = do
, "application/nonsense")] , "application/nonsense")]
post'' "/" "anything at all" `shouldRespondWith` 415 post'' "/" "anything at all" `shouldRespondWith` 415
type HeaderApi a = Header "MyHeader" a :> Delete
headerApi :: Proxy (HeaderApi a)
headerApi = Proxy
headerSpec :: Spec
headerSpec = describe "Servant.API.Header" $ do
let expectsInt :: Maybe Int -> EitherT (Int,String) IO ()
expectsInt (Just x) = when (x /= 5) $ error "Expected 5"
expectsInt Nothing = error "Expected an int"
let expectsString :: Maybe String -> EitherT (Int,String) IO ()
expectsString (Just x) = when (x /= "more from you") $ error "Expected more from you"
expectsString Nothing = error "Expected a string"
with (return (serve headerApi expectsInt)) $ do
let delete' x = Test.Hspec.Wai.request methodDelete x [("MyHeader" ,"5")]
it "passes the header to the handler (Int)" $
delete' "/" "" `shouldRespondWith` 204
with (return (serve headerApi expectsString)) $ do
let delete' x = Test.Hspec.Wai.request methodDelete x [("MyHeader" ,"more from you")]
it "passes the header to the handler (String)" $
delete' "/" "" `shouldRespondWith` 204
type RawApi = "foo" :> Raw type RawApi = "foo" :> Raw
rawApi :: Proxy RawApi rawApi :: Proxy RawApi