server/config: remove general tagging from Config

This commit is contained in:
Sönke Hahn 2016-01-13 16:54:15 +01:00
parent 188f4eca5f
commit 787c5b55a0
5 changed files with 44 additions and 73 deletions

View file

@ -38,8 +38,6 @@ module Servant.Server
-- * Config -- * Config
, Config(..) , Config(..)
, (.:.)
, Tagged(..)
-- * Default error type -- * Default error type
, ServantErr(..) , ServantErr(..)

View file

@ -28,10 +28,6 @@ data Config a where
(:.) :: x -> Config xs -> Config (x ': xs) (:.) :: x -> Config xs -> Config (x ': xs)
infixr 5 :. infixr 5 :.
(.:.) :: forall x xs . x -> Config xs -> Config (Tagged () x ': xs)
x .:. xs = (Tag x :: Tagged () x) :. xs
infixr 5 .:.
instance Show (Config '[]) where instance Show (Config '[]) where
show EmptyConfig = "EmptyConfig" show EmptyConfig = "EmptyConfig"
instance (Show a, Show (Config as)) => Show (Config (a ': as)) where instance (Show a, Show (Config as)) => Show (Config (a ': as)) where
@ -44,16 +40,13 @@ instance Eq (Config '[]) where
instance (Eq a, Eq (Config as)) => Eq (Config (a ': as)) where instance (Eq a, Eq (Config as)) => Eq (Config (a ': as)) where
x1 :. y1 == x2 :. y2 = x1 == x2 && y1 == y2 x1 :. y1 == x2 :. y2 = x1 == x2 && y1 == y2
newtype Tagged tag a = Tag a class HasConfigEntry (cfg :: [*]) (val :: *) where
deriving (Show, Eq) getConfigEntry :: Config cfg -> val
class HasConfigEntry (cfg :: [*]) tag (val :: *) where
getConfigEntry :: Proxy tag -> Config cfg -> val
instance OVERLAPPABLE_ instance OVERLAPPABLE_
HasConfigEntry xs tag val => HasConfigEntry (Tagged notItTag notIt ': xs) tag val where HasConfigEntry xs val => HasConfigEntry (notIt ': xs) val where
getConfigEntry proxy (_ :. xs) = getConfigEntry proxy xs getConfigEntry (_ :. xs) = getConfigEntry xs
instance OVERLAPPABLE_ instance OVERLAPPABLE_
HasConfigEntry (Tagged tag val ': xs) tag val where HasConfigEntry (val ': xs) val where
getConfigEntry Proxy (Tag x :. _) = x getConfigEntry (x :. _) = x

View file

@ -13,21 +13,16 @@ spec :: Spec
spec = do spec = do
describe "getConfigEntry" $ do describe "getConfigEntry" $ do
it "gets the config if a matching one exists" $ do it "gets the config if a matching one exists" $ do
let config = 'a' .:. EmptyConfig let config = 'a' :. EmptyConfig
getConfigEntry (Proxy :: Proxy ()) config `shouldBe` 'a' getConfigEntry config `shouldBe` 'a'
it "gets the first matching config" $ do it "gets the first matching config" $ do
let config = 'a' .:. 'b' .:. EmptyConfig let config = 'a' :. 'b' :. EmptyConfig
getConfigEntry (Proxy :: Proxy ()) config `shouldBe` 'a' getConfigEntry config `shouldBe` 'a'
it "allows to distinguish between different config entries with the same type by tag" $ do
let config = 'a' .:. (Tag 'b' :: Tagged "second" Char) :. EmptyConfig
getConfigEntry (Proxy :: Proxy ()) config `shouldBe` 'a'
getConfigEntry (Proxy :: Proxy "second") config `shouldBe` 'b'
it "does not typecheck if type does not exist" $ do it "does not typecheck if type does not exist" $ do
let config = 'a' .:. EmptyConfig let config = 'a' :. EmptyConfig
x = getConfigEntry (Proxy :: Proxy ()) config :: Bool x = getConfigEntry config :: Bool
shouldNotTypecheck x shouldNotTypecheck x
it "does not typecheck if tag does not exist" $ do it "does not typecheck if tag does not exist" $ do

View file

@ -16,7 +16,7 @@ import Servant.Server.UsingConfigSpec.TestCombinators
-- * API -- * API
type OneEntryAPI = type OneEntryAPI =
ExtractFromConfig () :> Get '[JSON] String ExtractFromConfig :> Get '[JSON] String
testServer :: String -> ExceptT ServantErr IO String testServer :: String -> ExceptT ServantErr IO String
testServer s = return s testServer s = return s
@ -25,32 +25,18 @@ oneEntryApp :: Application
oneEntryApp = oneEntryApp =
serve (Proxy :: Proxy OneEntryAPI) config testServer serve (Proxy :: Proxy OneEntryAPI) config testServer
where where
config = ("configEntry" :: String) .:. EmptyConfig config = ("configEntry" :: String) :. EmptyConfig
type OneEntryTwiceAPI = type OneEntryTwiceAPI =
"foo" :> ExtractFromConfig () :> Get '[JSON] String :<|> "foo" :> ExtractFromConfig :> Get '[JSON] String :<|>
"bar" :> ExtractFromConfig () :> Get '[JSON] String "bar" :> ExtractFromConfig :> Get '[JSON] String
oneEntryTwiceApp :: Application oneEntryTwiceApp :: Application
oneEntryTwiceApp = serve (Proxy :: Proxy OneEntryTwiceAPI) config $ oneEntryTwiceApp = serve (Proxy :: Proxy OneEntryTwiceAPI) config $
testServer :<|> testServer :<|>
testServer testServer
where where
config = ("configEntryTwice" :: String) .:. EmptyConfig config = ("configEntryTwice" :: String) :. EmptyConfig
type TwoDifferentEntries =
"foo" :> ExtractFromConfig "foo" :> Get '[JSON] String :<|>
"bar" :> ExtractFromConfig "bar" :> Get '[JSON] String
twoDifferentEntries :: Application
twoDifferentEntries = serve (Proxy :: Proxy TwoDifferentEntries) config $
testServer :<|>
testServer
where
config =
(Tag "firstEntry" :: Tagged "foo" String) :.
(Tag "secondEntry" :: Tagged "bar" String) :.
EmptyConfig
-- * tests -- * tests
@ -66,17 +52,12 @@ spec = do
get "/foo" `shouldRespondWith` "\"configEntryTwice\"" get "/foo" `shouldRespondWith` "\"configEntryTwice\""
get "/bar" `shouldRespondWith` "\"configEntryTwice\"" get "/bar" `shouldRespondWith` "\"configEntryTwice\""
with (return twoDifferentEntries) $ do
it "allows to retrieve different ConfigEntries for the same combinator" $ do
get "/foo" `shouldRespondWith` "\"firstEntry\""
get "/bar" `shouldRespondWith` "\"secondEntry\""
spec2 spec2
type InjectAPI = type InjectAPI =
InjectIntoConfig () :> "untagged" :> ExtractFromConfig () :> InjectIntoConfig :> "untagged" :> ExtractFromConfig :>
Get '[JSON] String :<|> Get '[JSON] String :<|>
InjectIntoConfig "tag" :> "tagged" :> ExtractFromConfig "tag" :> InjectIntoConfig :> "tagged" :> ExtractFromConfig :>
Get '[JSON] String Get '[JSON] String
injectApp :: Application injectApp :: Application
@ -99,21 +80,22 @@ spec2 = do
spec3 spec3
type SubConfigAPI = type SubConfigAPI =
"foo" :> ExtractFromConfig () :> Get '[JSON] String :<|> "foo" :> ExtractFromConfig :> Get '[JSON] String :<|>
SubConfig "sub" '[Tagged () String] :> SubConfig "sub" '[String] :>
"bar" :> ExtractFromConfig () :> Get '[JSON] String "bar" :> ExtractFromConfig :> Get '[JSON] String
subConfigApp :: Application subConfigApp :: Application
subConfigApp = serve (Proxy :: Proxy SubConfigAPI) config $ subConfigApp = serve (Proxy :: Proxy SubConfigAPI) config $
testServer :<|> testServer :<|>
testServer testServer
where where
config :: Config '[Tagged () String, Tagged () (Tagged "sub" (Config '[Tagged () String]))] config :: Config '[String, (Tagged "sub" (Config '[String]))]
config = config =
("firstEntry" :: String) .:. ("firstEntry" :: String) :.
(Tag (("secondEntry") .:. EmptyConfig)) .:. (Tag (("secondEntry" :: String) :. EmptyConfig)) :.
EmptyConfig EmptyConfig
spec3 :: Spec
spec3 = do spec3 = do
with (return subConfigApp) $ do with (return subConfigApp) $ do
it "allows to retrieve different ConfigEntries for the same combinator" $ do it "allows to retrieve different ConfigEntries for the same combinator" $ do

View file

@ -19,16 +19,16 @@ import Servant
import Servant.Server.Internal.Config import Servant.Server.Internal.Config
import Servant.Server.Internal.RoutingApplication import Servant.Server.Internal.RoutingApplication
data ExtractFromConfig (tag :: k) data ExtractFromConfig
instance forall subApi (c :: [*]) tag . instance forall subApi (c :: [*]) .
(HasServer subApi) => (HasServer subApi) =>
HasServer (ExtractFromConfig tag :> subApi) where HasServer (ExtractFromConfig :> subApi) where
type ServerT (ExtractFromConfig tag :> subApi) m = type ServerT (ExtractFromConfig :> subApi) m =
String -> ServerT subApi m String -> ServerT subApi m
type HasCfg (ExtractFromConfig tag :> subApi) c = type HasCfg (ExtractFromConfig :> subApi) c =
(HasConfigEntry c tag String, HasCfg subApi c) (HasConfigEntry c String, 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))
@ -36,17 +36,17 @@ instance forall subApi (c :: [*]) tag .
subProxy :: Proxy subApi subProxy :: Proxy subApi
subProxy = Proxy subProxy = Proxy
inject config f = f (getConfigEntry (Proxy :: Proxy tag) config) inject config f = f (getConfigEntry config)
data InjectIntoConfig (tag :: k) data InjectIntoConfig
instance (HasServer subApi) => instance (HasServer subApi) =>
HasServer (InjectIntoConfig (tag :: k) :> subApi) where HasServer (InjectIntoConfig :> subApi) where
type ServerT (InjectIntoConfig tag :> subApi) m = type ServerT (InjectIntoConfig :> subApi) m =
ServerT subApi m ServerT subApi m
type HasCfg (InjectIntoConfig tag :> subApi) c = type HasCfg (InjectIntoConfig :> subApi) c =
(HasCfg subApi (Tagged tag String ': c)) (HasCfg subApi (String ': c))
route Proxy config delayed = route Proxy config delayed =
route subProxy newConfig delayed route subProxy newConfig delayed
@ -54,17 +54,20 @@ instance (HasServer subApi) =>
subProxy :: Proxy subApi subProxy :: Proxy subApi
subProxy = Proxy subProxy = Proxy
newConfig = (Tag "injected" :: Tagged tag String) :. config newConfig = ("injected" :: String) :. config
data SubConfig (name :: Symbol) (subConfig :: [*]) data SubConfig (name :: Symbol) (subConfig :: [*])
newtype Tagged tag a = Tag a
deriving (Show, Eq)
instance (HasServer subApi) => instance (HasServer subApi) =>
HasServer (SubConfig name subConfig :> subApi) where HasServer (SubConfig name subConfig :> subApi) where
type ServerT (SubConfig name subConfig :> subApi) m = type ServerT (SubConfig name subConfig :> subApi) m =
ServerT subApi m ServerT subApi m
type HasCfg (SubConfig name subConfig :> subApi) config = type HasCfg (SubConfig name subConfig :> subApi) config =
(HasConfigEntry config () (Tagged name (Config subConfig)), HasCfg subApi subConfig) (HasConfigEntry config (Tagged name (Config subConfig)), HasCfg subApi subConfig)
route Proxy config delayed = route Proxy config delayed =
route subProxy subConfig delayed route subProxy subConfig delayed
@ -74,5 +77,5 @@ instance (HasServer subApi) =>
subConfig :: Config subConfig subConfig :: Config subConfig
subConfig = subConfig =
let Tag x = (getConfigEntry (Proxy :: Proxy ()) config) :: Tagged name (Config subConfig) let Tag x = getConfigEntry config :: Tagged name (Config subConfig)
in x in x