server: add test cases for config using combinators
This commit is contained in:
parent
1e4bd5feaa
commit
f5a0819990
2 changed files with 55 additions and 25 deletions
|
@ -13,27 +13,64 @@ import Servant.Server.UsingConfigSpec.CustomCombinator
|
||||||
|
|
||||||
-- * API
|
-- * API
|
||||||
|
|
||||||
type API =
|
data Tag1
|
||||||
CustomCombinator :> Get '[JSON] String
|
data Tag2
|
||||||
|
|
||||||
api :: Proxy API
|
type OneEntryAPI =
|
||||||
api = Proxy
|
CustomCombinator Tag1 :> Get '[JSON] String
|
||||||
|
|
||||||
testServer :: Server API
|
testServer :: Server OneEntryAPI
|
||||||
testServer (CustomConfig s) = return s
|
testServer (CustomConfig s) = return s
|
||||||
|
|
||||||
app :: Application
|
oneEntryApp :: Application
|
||||||
app =
|
oneEntryApp =
|
||||||
serve api config testServer
|
serve (Proxy :: Proxy OneEntryAPI) config testServer
|
||||||
where
|
where
|
||||||
config :: Config '[ConfigEntry Tag CustomConfig]
|
config :: Config '[ConfigEntry Tag1 CustomConfig]
|
||||||
config = CustomConfig "configValue" .:. EmptyConfig
|
config = CustomConfig "configValue" .:. EmptyConfig
|
||||||
|
|
||||||
|
type OneEntryTwiceAPI =
|
||||||
|
"foo" :> CustomCombinator Tag1 :> Get '[JSON] String :<|>
|
||||||
|
"bar" :> CustomCombinator Tag1 :> Get '[JSON] String
|
||||||
|
|
||||||
|
oneEntryTwiceApp :: Application
|
||||||
|
oneEntryTwiceApp = serve (Proxy :: Proxy OneEntryTwiceAPI) config $
|
||||||
|
testServer :<|>
|
||||||
|
testServer
|
||||||
|
where
|
||||||
|
config :: Config '[ConfigEntry Tag1 CustomConfig]
|
||||||
|
config = CustomConfig "configValueTwice" .:. EmptyConfig
|
||||||
|
|
||||||
|
type TwoDifferentEntries =
|
||||||
|
"foo" :> CustomCombinator Tag1 :> Get '[JSON] String :<|>
|
||||||
|
"bar" :> CustomCombinator Tag2 :> Get '[JSON] String
|
||||||
|
|
||||||
|
twoDifferentEntries :: Application
|
||||||
|
twoDifferentEntries = serve (Proxy :: Proxy TwoDifferentEntries) config $
|
||||||
|
testServer :<|>
|
||||||
|
testServer
|
||||||
|
where
|
||||||
|
config :: Config '[ConfigEntry Tag1 CustomConfig, ConfigEntry Tag2 CustomConfig]
|
||||||
|
config =
|
||||||
|
CustomConfig "firstConfigValue" .:.
|
||||||
|
CustomConfig "secondConfigValue" .:.
|
||||||
|
EmptyConfig
|
||||||
|
|
||||||
-- * tests
|
-- * tests
|
||||||
|
|
||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = do
|
spec = do
|
||||||
describe "using Config in a custom combinator" $ do
|
describe "using Config in a custom combinator" $ do
|
||||||
with (return app) $ do
|
with (return oneEntryApp) $ do
|
||||||
it "allows to retrieve the ConfigEntry" $ do
|
it "allows to retrieve a ConfigEntry" $ do
|
||||||
get "/" `shouldRespondWith` "\"configValue\""
|
get "/" `shouldRespondWith` "\"configValue\""
|
||||||
|
|
||||||
|
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\""
|
||||||
|
|
|
@ -13,29 +13,22 @@
|
||||||
-- the config.
|
-- the config.
|
||||||
module Servant.Server.UsingConfigSpec.CustomCombinator where
|
module Servant.Server.UsingConfigSpec.CustomCombinator where
|
||||||
|
|
||||||
-- import Network.Wai
|
|
||||||
-- import Test.Hspec (Spec, describe, it)
|
|
||||||
-- import Test.Hspec.Wai
|
|
||||||
|
|
||||||
import Servant
|
import Servant
|
||||||
import Servant.Server.Internal.Config
|
import Servant.Server.Internal.Config
|
||||||
-- import Servant.Server.Internal.Router
|
|
||||||
import Servant.Server.Internal.RoutingApplication
|
import Servant.Server.Internal.RoutingApplication
|
||||||
|
|
||||||
data CustomCombinator
|
data CustomCombinator (tag :: *)
|
||||||
|
|
||||||
data CustomConfig = CustomConfig String
|
data CustomConfig = CustomConfig String
|
||||||
|
|
||||||
data Tag
|
instance forall subApi (c :: [*]) tag .
|
||||||
|
|
||||||
instance forall subApi (c :: [*]) .
|
|
||||||
(HasServer subApi) =>
|
(HasServer subApi) =>
|
||||||
HasServer (CustomCombinator :> subApi) where
|
HasServer (CustomCombinator tag :> subApi) where
|
||||||
|
|
||||||
type ServerT (CustomCombinator :> subApi) m =
|
type ServerT (CustomCombinator tag :> subApi) m =
|
||||||
CustomConfig -> ServerT subApi m
|
CustomConfig -> ServerT subApi m
|
||||||
type HasCfg (CustomCombinator :> subApi) c =
|
type HasCfg (CustomCombinator tag :> subApi) c =
|
||||||
(HasConfigEntry c Tag CustomConfig, HasCfg subApi c)
|
(HasConfigEntry c tag CustomConfig, HasCfg subApi c)
|
||||||
|
|
||||||
route Proxy config delayed =
|
route Proxy config delayed =
|
||||||
route subProxy config (fmap (inject config) delayed :: Delayed (Server subApi))
|
route subProxy config (fmap (inject config) delayed :: Delayed (Server subApi))
|
||||||
|
@ -43,5 +36,5 @@ instance forall subApi (c :: [*]) .
|
||||||
subProxy :: Proxy subApi
|
subProxy :: Proxy subApi
|
||||||
subProxy = Proxy
|
subProxy = Proxy
|
||||||
|
|
||||||
inject config f = f (getConfigEntry (Proxy :: Proxy Tag) config)
|
inject config f = f (getConfigEntry (Proxy :: Proxy tag) config)
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue