servant-ekg/test/Servant/EkgSpec.hs

127 lines
4.1 KiB
Haskell
Raw Normal View History

{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
2016-05-13 14:56:09 +02:00
module Servant.EkgSpec (spec) where
2015-05-01 08:09:23 +02:00
import Data.Aeson
import qualified Data.HashMap.Strict as H
import Data.Monoid ((<>))
2015-05-01 08:09:23 +02:00
import Data.Proxy
import Data.Text
import GHC.Generics
import Network.HTTP.Client (defaultManagerSettings,
newManager)
2015-05-01 08:09:23 +02:00
import Network.Wai
import Network.Wai.Handler.Warp
import Servant
2016-05-13 14:56:09 +02:00
import Servant.Client
#if MIN_VERSION_servant(0,15,0)
import Servant.Test.ComprehensiveAPI (comprehensiveAPI)
#else
import Servant.API.Internal.Test.ComprehensiveAPI (comprehensiveAPI)
#endif
2015-05-01 08:09:23 +02:00
import System.Metrics
2016-05-13 14:56:09 +02:00
import Test.Hspec
2015-05-01 08:09:23 +02:00
import Servant.Ekg
2019-02-27 19:55:46 +01:00
#if !MIN_VERSION_servant_client(0,16,0)
#define ClientError ServantError
#endif
2016-05-13 14:56:09 +02:00
-- * Spec
spec :: Spec
spec = describe "servant-ekg" $ do
2017-01-30 19:46:54 +01:00
let getEp :<|> postEp :<|> deleteEp = client testApi
2016-05-13 14:56:09 +02:00
it "collects number of request" $
withApp $ \port store -> do
2016-05-13 14:56:09 +02:00
mgr <- newManager defaultManagerSettings
2019-02-27 19:55:46 +01:00
let runFn :: ClientM a -> IO (Either ClientError a)
2019-02-09 18:50:52 +01:00
runFn fn = runClientM fn (mkClientEnv mgr (BaseUrl Http "localhost" port ""))
2017-01-30 19:46:54 +01:00
_ <- runFn $ getEp "name" Nothing
_ <- runFn $ postEp (Greet "hi")
_ <- runFn $ deleteEp "blah"
m <- sampleAll store
case H.lookup "servant.path.hello.:name.GET.responses.2XX" m of
2016-05-13 14:56:09 +02:00
Nothing -> fail "Expected some value"
Just v -> v `shouldBe` Counter 1
case H.lookup "servant.path.greet.POST.responses.2XX" m of
2017-01-30 19:46:54 +01:00
Nothing -> fail "Expected some value"
Just v -> v `shouldBe` Counter 1
case H.lookup "servant.path.greet.:greetid.DELETE.responses.2XX" m of
2017-01-30 19:46:54 +01:00
Nothing -> fail "Expected some value"
Just v -> v `shouldBe` Counter 1
2016-05-13 14:56:09 +02:00
2016-05-13 17:54:18 +02:00
it "is comprehensive" $ do
_typeLevelTest <- monitorEndpoints comprehensiveAPI =<< newStore
2016-05-13 17:54:18 +02:00
True `shouldBe` True
it "enumerates the parts of an API correctly" $
enumerateEndpoints testApi `shouldBe` [
APIEndpoint ["hello",":name"] "GET",
APIEndpoint ["greet"] "POST",
APIEndpoint ["greet",":greetid"] "DELETE"
]
2016-05-13 14:56:09 +02:00
-- * Example
-- | A greet message data type
newtype Greet = Greet { _msg :: Text }
deriving (Generic, Show)
instance FromJSON Greet
instance ToJSON Greet
-- API specification
type TestApi =
-- GET /hello/:name?capital={true, false} returns a Greet as JSON
2016-05-13 12:27:26 +02:00
"hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get '[JSON] Greet
-- POST /greet with a Greet as JSON in the request body,
-- returns a Greet as JSON
2016-05-13 12:27:26 +02:00
:<|> "greet" :> ReqBody '[JSON] Greet :> Post '[JSON] Greet
-- DELETE /greet/:greetid
:<|> "greet" :> Capture "greetid" Text :> Delete '[JSON] NoContent
testApi :: Proxy TestApi
testApi = Proxy
-- Server-side handlers.
--
-- There's one handler per endpoint, which, just like in the type
-- that represents the API, are glued together using :<|>.
--
-- Each handler runs in the 'EitherT (Int, String) IO' monad.
server :: Server TestApi
server = helloH :<|> postGreetH :<|> deleteGreetH
where helloH name Nothing = helloH name (Just False)
helloH name (Just False) = return . Greet $ "Hello, " <> name
helloH name (Just True) = return . Greet . toUpper $ "Hello, " <> name
2015-05-01 08:09:23 +02:00
postGreetH = return
deleteGreetH _ = return NoContent
-- Turn the server into a WAI app. 'serve' is provided by servant,
-- more precisely by the Servant.Server module.
test :: Application
test = serve testApi server
withApp :: (Port -> Store -> IO a) -> IO a
2016-05-13 14:56:09 +02:00
withApp a = do
ekg <- newStore
monitorEndpoints' <- monitorEndpoints testApi ekg
withApplication (return $ monitorEndpoints' test) $ \p -> a p ekg