servant-server tests: tiny refactoring

This commit is contained in:
Sönke Hahn 2016-01-10 15:39:55 +01:00
parent dcd2c8078c
commit 1e4bd5feaa
2 changed files with 49 additions and 34 deletions

View file

@ -1,11 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Servant.Server.UsingConfigSpec where
@ -14,34 +9,7 @@ import Test.Hspec (Spec, describe, it)
import Test.Hspec.Wai
import Servant
import Servant.Server.Internal.Config
import Servant.Server.Internal.Router
import Servant.Server.Internal.RoutingApplication
-- * custom test combinator
data CustomCombinator
data CustomConfig = CustomConfig String
data Tag
instance forall subApi (c :: [*]) .
(HasServer subApi) =>
HasServer (CustomCombinator :> subApi) where
type ServerT (CustomCombinator :> subApi) m =
CustomConfig -> ServerT subApi m
type HasCfg (CustomCombinator :> subApi) c =
(HasConfigEntry c Tag CustomConfig, HasCfg subApi c)
route Proxy config delayed =
route subProxy config (fmap (inject config) delayed :: Delayed (Server subApi))
where
subProxy :: Proxy subApi
subProxy = Proxy
inject config f = f (getConfigEntry (Proxy :: Proxy Tag) config)
import Servant.Server.UsingConfigSpec.CustomCombinator
-- * API
@ -59,7 +27,7 @@ app =
serve api config testServer
where
config :: Config '[ConfigEntry Tag CustomConfig]
config = CustomConfig "configValue" .: EmptyConfig
config = CustomConfig "configValue" .:. EmptyConfig
-- * tests

View file

@ -0,0 +1,47 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{- LANGUAGE OverloadedStrings #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{- LANGUAGE UndecidableInstances #-}
-- | This is a custom combinator for S.S.UsingConfigSpec. It's split up into
-- its own module to be able to test how exactly module import work when using
-- the config.
module Servant.Server.UsingConfigSpec.CustomCombinator where
-- import Network.Wai
-- import Test.Hspec (Spec, describe, it)
-- import Test.Hspec.Wai
import Servant
import Servant.Server.Internal.Config
-- import Servant.Server.Internal.Router
import Servant.Server.Internal.RoutingApplication
data CustomCombinator
data CustomConfig = CustomConfig String
data Tag
instance forall subApi (c :: [*]) .
(HasServer subApi) =>
HasServer (CustomCombinator :> subApi) where
type ServerT (CustomCombinator :> subApi) m =
CustomConfig -> ServerT subApi m
type HasCfg (CustomCombinator :> subApi) c =
(HasConfigEntry c Tag CustomConfig, HasCfg subApi c)
route Proxy config delayed =
route subProxy config (fmap (inject config) delayed :: Delayed (Server subApi))
where
subProxy :: Proxy subApi
subProxy = Proxy
inject config f = f (getConfigEntry (Proxy :: Proxy Tag) config)