Merge pull request #2 from epsilonhalbe/master

compatibility to servant 0.8/0.9
This commit is contained in:
Julian Arni 2017-01-30 10:11:39 -08:00 committed by GitHub
commit 787bfb5c1b
4 changed files with 24 additions and 3 deletions

1
.gitignore vendored
View File

@ -3,3 +3,4 @@
.cabal-sandbox/*
*dist/
*dist-newstyle/
.stack-work/

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
@ -160,3 +161,8 @@ instance ReflectMethod method => HasEndpoint (Verb method status cts a) where
instance HasEndpoint (Raw) where
getEndpoint _ _ = Just ([],"RAW")
#if MIN_VERSION_servant(0,8,1)
instance HasEndpoint (sub :: *) => HasEndpoint (CaptureAll (h :: Symbol) a :> sub) where
getEndpoint _ = getEndpoint (Proxy :: Proxy sub)
#endif

View File

@ -17,9 +17,9 @@ source-repository HEAD
library
exposed-modules: Servant.Ekg
hs-source-dirs: lib
build-depends: base >=4.7 && <4.9
build-depends: base >=4.7 && < 4.10
, ekg-core
, servant > 0.5 && < 0.8
, servant > 0.5 && < 0.10
, http-types
, text
, time

View File

@ -1,6 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
@ -9,7 +9,9 @@
module Servant.EkgSpec (spec) where
import Control.Concurrent
#if !MIN_VERSION_servant(0,9,0)
import Control.Monad.Trans.Except
#endif
import Data.Aeson
import Data.Monoid
import Data.Proxy
@ -39,7 +41,11 @@ spec = describe "servant-ekg" $ do
it "collects number of request" $ do
withApp $ \port mvar -> do
mgr <- newManager defaultManagerSettings
#if MIN_VERSION_servant(0,9,0)
Right _result <- runClientM (getEp "name" Nothing) (ClientEnv mgr (BaseUrl Http "localhost" port ""))
#else
_result <- runExceptT $ getEp "name" Nothing mgr (BaseUrl Http "localhost" port "")
#endif
m <- readMVar mvar
case H.lookup "hello.:name.GET" m of
Nothing -> fail "Expected some value"
@ -69,7 +75,11 @@ type TestApi =
:<|> "greet" :> ReqBody '[JSON] Greet :> Post '[JSON] Greet
-- DELETE /greet/:greetid
#if MIN_VERSION_servant(0,8,0)
:<|> "greet" :> Capture "greetid" Text :> Delete '[JSON] NoContent
#else
:<|> "greet" :> Capture "greetid" Text :> Delete '[JSON] ()
#endif
testApi :: Proxy TestApi
testApi = Proxy
@ -89,7 +99,11 @@ server = helloH :<|> postGreetH :<|> deleteGreetH
postGreetH = return
#if MIN_VERSION_servant(0,8,0)
deleteGreetH _ = return NoContent
#else
deleteGreetH _ = return ()
#endif
-- Turn the server into a WAI app. 'serve' is provided by servant,
-- more precisely by the Servant.Server module.