2016-01-09 17:22:52 +01:00
|
|
|
{-# LANGUAGE DataKinds #-}
|
2016-01-10 16:40:56 +01:00
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
2016-01-09 17:22:52 +01:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE TypeOperators #-}
|
|
|
|
|
|
|
|
module Servant.Server.UsingConfigSpec where
|
|
|
|
|
|
|
|
import Network.Wai
|
|
|
|
import Test.Hspec (Spec, describe, it)
|
|
|
|
import Test.Hspec.Wai
|
|
|
|
|
|
|
|
import Servant
|
2016-01-10 15:39:55 +01:00
|
|
|
import Servant.Server.UsingConfigSpec.CustomCombinator
|
2016-01-09 17:22:52 +01:00
|
|
|
|
|
|
|
-- * API
|
|
|
|
|
2016-01-10 16:40:56 +01:00
|
|
|
newtype Wrapped a = Wrap { unwrap :: a }
|
|
|
|
|
2016-01-10 16:50:17 +01:00
|
|
|
instance ToCustomConfig (Wrapped String) where
|
2016-01-10 16:40:56 +01:00
|
|
|
toCustomConfig = unwrap
|
2016-01-09 17:22:52 +01:00
|
|
|
|
2016-01-10 15:59:33 +01:00
|
|
|
type OneEntryAPI =
|
2016-01-10 16:50:17 +01:00
|
|
|
CustomCombinator String :> Get '[JSON] String
|
2016-01-09 17:22:52 +01:00
|
|
|
|
2016-01-10 15:59:33 +01:00
|
|
|
testServer :: Server OneEntryAPI
|
2016-01-10 16:50:17 +01:00
|
|
|
testServer s = return s
|
2016-01-09 17:22:52 +01:00
|
|
|
|
2016-01-10 15:59:33 +01:00
|
|
|
oneEntryApp :: Application
|
|
|
|
oneEntryApp =
|
|
|
|
serve (Proxy :: Proxy OneEntryAPI) config testServer
|
2016-01-09 17:22:52 +01:00
|
|
|
where
|
2016-01-10 16:50:17 +01:00
|
|
|
config :: Config '[String]
|
|
|
|
config = "configValue" :. EmptyConfig
|
2016-01-09 17:22:52 +01:00
|
|
|
|
2016-01-10 15:59:33 +01:00
|
|
|
type OneEntryTwiceAPI =
|
2016-01-10 16:50:17 +01:00
|
|
|
"foo" :> CustomCombinator String :> Get '[JSON] String :<|>
|
|
|
|
"bar" :> CustomCombinator String :> Get '[JSON] String
|
2016-01-10 15:59:33 +01:00
|
|
|
|
|
|
|
oneEntryTwiceApp :: Application
|
|
|
|
oneEntryTwiceApp = serve (Proxy :: Proxy OneEntryTwiceAPI) config $
|
|
|
|
testServer :<|>
|
|
|
|
testServer
|
|
|
|
where
|
2016-01-10 16:50:17 +01:00
|
|
|
config :: Config '[String]
|
|
|
|
config = "configValueTwice" :. EmptyConfig
|
2016-01-10 15:59:33 +01:00
|
|
|
|
|
|
|
type TwoDifferentEntries =
|
2016-01-10 16:50:17 +01:00
|
|
|
"foo" :> CustomCombinator String :> Get '[JSON] String :<|>
|
|
|
|
"bar" :> CustomCombinator (Wrapped String) :> Get '[JSON] String
|
2016-01-10 15:59:33 +01:00
|
|
|
|
|
|
|
twoDifferentEntries :: Application
|
|
|
|
twoDifferentEntries = serve (Proxy :: Proxy TwoDifferentEntries) config $
|
|
|
|
testServer :<|>
|
|
|
|
testServer
|
|
|
|
where
|
2016-01-10 16:50:17 +01:00
|
|
|
config :: Config '[String, Wrapped String]
|
2016-01-10 15:59:33 +01:00
|
|
|
config =
|
2016-01-10 16:50:17 +01:00
|
|
|
"firstConfigValue" :.
|
|
|
|
Wrap "secondConfigValue" :.
|
2016-01-10 15:59:33 +01:00
|
|
|
EmptyConfig
|
|
|
|
|
2016-01-09 17:22:52 +01:00
|
|
|
-- * tests
|
|
|
|
|
|
|
|
spec :: Spec
|
|
|
|
spec = do
|
|
|
|
describe "using Config in a custom combinator" $ do
|
2016-01-10 15:59:33 +01:00
|
|
|
with (return oneEntryApp) $ do
|
|
|
|
it "allows to retrieve a ConfigEntry" $ do
|
2016-01-09 17:22:52 +01:00
|
|
|
get "/" `shouldRespondWith` "\"configValue\""
|
2016-01-10 15:59:33 +01:00
|
|
|
|
|
|
|
with (return oneEntryTwiceApp) $ do
|
|
|
|
it "allows to retrieve the same ConfigEntry twice" $ do
|
|
|
|
get "/foo" `shouldRespondWith` "\"configValueTwice\""
|
|
|
|
get "/bar" `shouldRespondWith` "\"configValueTwice\""
|
|
|
|
|
|
|
|
with (return twoDifferentEntries) $ do
|
|
|
|
it "allows to retrieve different ConfigEntries for the same combinator" $ do
|
|
|
|
get "/foo" `shouldRespondWith` "\"firstConfigValue\""
|
|
|
|
get "/bar" `shouldRespondWith` "\"secondConfigValue\""
|