use TestServer better

This commit is contained in:
Sönke Hahn 2016-01-04 19:04:10 +01:00
parent 82887d7d3b
commit 5329aa015e
5 changed files with 34 additions and 18 deletions

View file

@ -1,9 +1,12 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
-- | Testing works very differently under ghc and ghcjs. This module acts as a
-- CPP switch and import different modules depending on the used compiler (ghc
-- or ghcjs). Both imported modules provide the same API.
module Servant.Client.TestServer ( module Servant.Client.TestServer (
buildTestServer, buildTestServer,
TestServer(..), TestServer(..),
withTestServer, withServer,
)where )where
#ifdef __GHCJS__ #ifdef __GHCJS__

View file

@ -14,8 +14,8 @@ import Servant.Client.TestServer.Types
buildTestServer :: IO () buildTestServer :: IO ()
buildTestServer = return () buildTestServer = return ()
withTestServer :: TestServer -> (BaseUrl -> IO a) -> IO a withServer :: TestServer -> (BaseUrl -> IO a) -> IO a
withTestServer (TestServer _ app) action = withServer (TestServer _ app) action =
bracket (startWaiApp app) endWaiApp $ \ (_, url) -> bracket (startWaiApp app) endWaiApp $ \ (_, url) ->
action url action url

View file

@ -16,8 +16,8 @@ buildTestServer = do
ExitSuccess <- waitForProcess process ExitSuccess <- waitForProcess process
return () return ()
withTestServer :: TestServer -> (BaseUrl -> IO a) -> IO a withServer :: TestServer -> (BaseUrl -> IO a) -> IO a
withTestServer (TestServer testServerName _) action = do withServer (TestServer testServerName _) action = do
bracket start stop $ \ (port, _) -> action (BaseUrl Http "localhost" port ("/" ++ testServerName)) bracket start stop $ \ (port, _) -> action (BaseUrl Http "localhost" port ("/" ++ testServerName))
where where
start :: IO (Int, ProcessHandle) start :: IO (Int, ProcessHandle)

View file

@ -12,13 +12,13 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-} {-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fcontext-stack=100 #-} {-# OPTIONS_GHC -fcontext-stack=100 #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Servant.ClientSpec where module Servant.ClientSpec where
@ -41,9 +41,9 @@ import Network.HTTP.Types (Status (..), badRequest400,
methodGet, ok200, status400) methodGet, ok200, status400)
import Network.Wai (responseLBS) import Network.Wai (responseLBS)
import System.IO.Unsafe (unsafePerformIO) import System.IO.Unsafe (unsafePerformIO)
import Test.HUnit
import Test.Hspec import Test.Hspec
import Test.Hspec.QuickCheck import Test.Hspec.QuickCheck
import Test.HUnit
import Test.QuickCheck import Test.QuickCheck
import Servant.API import Servant.API
@ -59,6 +59,23 @@ spec = do
failSpec failSpec
errorSpec errorSpec
lookupTestServer :: String -> TestServer
lookupTestServer name = case lookup name mapping of
Nothing -> error ("test server not found: " ++ name)
Just testServer -> testServer
where
mapping :: [(String, TestServer)]
mapping = map (\ server -> (testServerName server, server)) allTestServers
allTestServers =
server :
errorServer :
failServer :
[]
withTestServer :: String -> (BaseUrl -> IO a) -> IO a
withTestServer = withServer . lookupTestServer
-- * test data types -- * test data types
data Person = Person { data Person = Person {
@ -149,7 +166,7 @@ manager :: C.Manager
manager = unsafePerformIO $ C.newManager C.defaultManagerSettings manager = unsafePerformIO $ C.newManager C.defaultManagerSettings
sucessSpec :: Spec sucessSpec :: Spec
sucessSpec = around (withTestServer server) $ do sucessSpec = around (withTestServer "server") $ do
it "Servant.API.Get" $ \baseUrl -> do it "Servant.API.Get" $ \baseUrl -> do
let getGet = getNth (Proxy :: Proxy 0) $ client api baseUrl manager let getGet = getNth (Proxy :: Proxy 0) $ client api baseUrl manager
@ -242,7 +259,7 @@ errorServer = TestServer "errorServer" $ serve errorApi $
errorSpec :: Spec errorSpec :: Spec
errorSpec = errorSpec =
around (withTestServer errorServer) $ do around (withTestServer "errorServer") $ do
describe "error status codes" $ describe "error status codes" $
it "reports error statuses correctly" $ \baseUrl -> do it "reports error statuses correctly" $ \baseUrl -> do
let delete :<|> get :<|> post :<|> put = let delete :<|> get :<|> post :<|> put =
@ -253,7 +270,7 @@ errorSpec =
responseStatus `shouldBe` Status 500 "error message" responseStatus `shouldBe` Status 500 "error message"
failSpec :: Spec failSpec :: Spec
failSpec = around (withTestServer failServer) $ do failSpec = around (withTestServer "failServer") $ do
context "client returns errors appropriately" $ do context "client returns errors appropriately" $ do
it "reports FailureResponse" $ \baseUrl -> do it "reports FailureResponse" $ \baseUrl -> do

View file

@ -17,15 +17,11 @@ main = do
setBeforeMainLoop (print port >> hFlush stdout) $ setBeforeMainLoop (print port >> hFlush stdout) $
defaultSettings defaultSettings
runSettingsSocket settings socket $ runSettingsSocket settings socket $
serve testServerApi $ serve testServerApi $ \ testServerName ->
testServerApp server :<|> testServerApp $ lookupTestServer testServerName
testServerApp errorServer :<|>
testServerApp failServer
type TestServerApi = type TestServerApi =
"server" :> Raw :<|> Capture "testServerName" String :> Raw
"errorServer" :> Raw :<|>
"failServer" :> Raw
testServerApi :: Proxy TestServerApi testServerApi :: Proxy TestServerApi
testServerApi = Proxy testServerApi = Proxy