Implement HasServer (NamedRoutes routes)
We define `ServerT (NamedRoutes api) m` as `api (AsServerT m)`, so that the server of an record-defined API is a record of handlers. The implementation piggy backs on the instance for “vanilla” servant types with `(:<|>)`, using the `GServantProduct` for converting backd and forth between the record / vanilla servers. The main difficulty is that GHC needs to know that this operation is legit, which can be expressed as the fact that: ``` GToServant (Rep (ServerT (NamedRoutes api))) m ~ ServerT (GToServant (Rep (api AsApi))) m ``` plus a few additional constraints. This is easy enough for `route`, as we know that `m ~ Handler`. But in the case of `hoistServerWithContext`, the two involved monads are unknown ; in other words, this constraint needs to hold `forall m.` Switching `-XQuantifiedConstraints` on is not sufficient, as our constraints involve type families (`Rep` and `ServerT`). Our trick is to use an intermediary typeclass, `GServer`, as a provider of evidence (in the form of a `Dict`) that our constraints are indeed satisfied for a particular monad. The only instance of `GServer` is defined along with it, so it is practically invisible to users.
This commit is contained in:
parent
94cccffc75
commit
49c7dd2e8d
3 changed files with 103 additions and 11 deletions
|
@ -1,5 +1,6 @@
|
||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE PolyKinds #-}
|
{-# LANGUAGE PolyKinds #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
|
@ -16,6 +17,8 @@ import Network.Wai
|
||||||
import Network.Wai.Handler.Warp
|
import Network.Wai.Handler.Warp
|
||||||
|
|
||||||
import Servant
|
import Servant
|
||||||
|
import Servant.Server.Generic ()
|
||||||
|
import Servant.API.Generic
|
||||||
|
|
||||||
-- * Example
|
-- * Example
|
||||||
|
|
||||||
|
@ -38,6 +41,14 @@ type TestApi =
|
||||||
-- DELETE /greet/:greetid
|
-- DELETE /greet/:greetid
|
||||||
:<|> "greet" :> Capture "greetid" Text :> Delete '[JSON] NoContent
|
:<|> "greet" :> Capture "greetid" Text :> Delete '[JSON] NoContent
|
||||||
|
|
||||||
|
:<|> NamedRoutes OtherRoutes
|
||||||
|
|
||||||
|
data OtherRoutes mode = OtherRoutes
|
||||||
|
{ version :: mode :- Get '[JSON] Int
|
||||||
|
, bye :: mode :- "bye" :> Capture "name" Text :> Get '[JSON] Text
|
||||||
|
}
|
||||||
|
deriving Generic
|
||||||
|
|
||||||
testApi :: Proxy TestApi
|
testApi :: Proxy TestApi
|
||||||
testApi = Proxy
|
testApi = Proxy
|
||||||
|
|
||||||
|
@ -48,9 +59,13 @@ testApi = Proxy
|
||||||
--
|
--
|
||||||
-- Each handler runs in the 'Handler' monad.
|
-- Each handler runs in the 'Handler' monad.
|
||||||
server :: Server TestApi
|
server :: Server TestApi
|
||||||
server = helloH :<|> postGreetH :<|> deleteGreetH
|
server = helloH :<|> postGreetH :<|> deleteGreetH :<|> otherRoutes
|
||||||
|
where otherRoutes = OtherRoutes {..}
|
||||||
|
|
||||||
where helloH name Nothing = helloH name (Just False)
|
bye name = pure $ "Bye, " <> name <> " !"
|
||||||
|
version = pure 42
|
||||||
|
|
||||||
|
helloH name Nothing = helloH name (Just False)
|
||||||
helloH name (Just False) = return . Greet $ "Hello, " <> name
|
helloH name (Just False) = return . Greet $ "Hello, " <> name
|
||||||
helloH name (Just True) = return . Greet . toUpper $ "Hello, " <> name
|
helloH name (Just True) = return . Greet . toUpper $ "Hello, " <> name
|
||||||
|
|
||||||
|
|
|
@ -62,6 +62,7 @@ library
|
||||||
build-depends:
|
build-depends:
|
||||||
base >= 4.9 && < 4.16
|
base >= 4.9 && < 4.16
|
||||||
, bytestring >= 0.10.8.1 && < 0.12
|
, bytestring >= 0.10.8.1 && < 0.12
|
||||||
|
, constraints
|
||||||
, containers >= 0.5.7.1 && < 0.7
|
, containers >= 0.5.7.1 && < 0.7
|
||||||
, mtl >= 2.2.2 && < 2.3
|
, mtl >= 2.2.2 && < 2.3
|
||||||
, text >= 1.2.3.0 && < 1.3
|
, text >= 1.2.3.0 && < 1.3
|
||||||
|
|
|
@ -1,9 +1,17 @@
|
||||||
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
|
{-# LANGUAGE AllowAmbiguousTypes #-}
|
||||||
{-# LANGUAGE ConstraintKinds #-}
|
{-# LANGUAGE ConstraintKinds #-}
|
||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE DefaultSignatures #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
|
{-# LANGUAGE InstanceSigs #-}
|
||||||
{-# LANGUAGE KindSignatures #-}
|
{-# LANGUAGE KindSignatures #-}
|
||||||
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
|
{-# LANGUAGE QuantifiedConstraints #-}
|
||||||
{-# LANGUAGE RankNTypes #-}
|
{-# LANGUAGE RankNTypes #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
{-# LANGUAGE TypeApplications #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
|
@ -16,13 +24,20 @@ module Servant.Server.Generic (
|
||||||
genericServeTWithContext,
|
genericServeTWithContext,
|
||||||
genericServer,
|
genericServer,
|
||||||
genericServerT,
|
genericServerT,
|
||||||
|
-- * Internal machinery
|
||||||
|
GServerConstraints,
|
||||||
|
GServer,
|
||||||
|
-- * Re-exports
|
||||||
|
NamedRoutes
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Data.Constraint
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
(Proxy (..))
|
(Proxy (..))
|
||||||
|
|
||||||
import Servant.API.Generic
|
import Servant.API.Generic
|
||||||
import Servant.Server
|
import Servant.Server
|
||||||
|
import Servant.Server.Internal
|
||||||
|
|
||||||
-- | A type that specifies that an API record contains a server implementation.
|
-- | A type that specifies that an API record contains a server implementation.
|
||||||
data AsServerT (m :: * -> *)
|
data AsServerT (m :: * -> *)
|
||||||
|
@ -97,3 +112,64 @@ genericServerT
|
||||||
=> routes (AsServerT m)
|
=> routes (AsServerT m)
|
||||||
-> ToServant routes (AsServerT m)
|
-> ToServant routes (AsServerT m)
|
||||||
genericServerT = toServant
|
genericServerT = toServant
|
||||||
|
|
||||||
|
-- | Set of constraints required to convert to / from vanilla server types.
|
||||||
|
type GServerConstraints api m =
|
||||||
|
( ToServant api (AsServerT m) ~ ServerT (ToServantApi api) m
|
||||||
|
, GServantProduct (Rep (api (AsServerT m)))
|
||||||
|
)
|
||||||
|
|
||||||
|
-- | This class is a necessary evil: in the implementation of 'HasServer' for
|
||||||
|
-- @'NamedRoutes' api@, we essentially need the quantified constraint @forall
|
||||||
|
-- m. 'GServerConstraints' m@ to hold.
|
||||||
|
--
|
||||||
|
-- We cannot require do that directly as the definition of 'GServerConstraints'
|
||||||
|
-- contains type family applications ('Rep' and 'ServerT'). The trick is to hide
|
||||||
|
-- those type family applications behind a typeclass providing evidence for
|
||||||
|
-- @'GServerConstraints' api m@ in the form of a dictionary, and require that
|
||||||
|
-- @forall m. 'GServer' api m@ instead.
|
||||||
|
--
|
||||||
|
-- Users shouldn't have to worry about this class, as the only possible instance
|
||||||
|
-- is provided in this module for all record APIs.
|
||||||
|
|
||||||
|
class GServer (api :: * -> *) (m :: * -> *) where
|
||||||
|
proof :: Dict (GServerConstraints api m)
|
||||||
|
|
||||||
|
instance
|
||||||
|
( ToServant api (AsServerT m) ~ ServerT (ToServantApi api) m
|
||||||
|
, GServantProduct (Rep (api (AsServerT m)))
|
||||||
|
) => GServer api m where
|
||||||
|
proof = Dict
|
||||||
|
|
||||||
|
instance
|
||||||
|
( HasServer (ToServantApi api) context
|
||||||
|
, forall m. Generic (api (AsServerT m))
|
||||||
|
, forall m. GServer api m
|
||||||
|
) => HasServer (NamedRoutes api) context where
|
||||||
|
|
||||||
|
type ServerT (NamedRoutes api) m = api (AsServerT m)
|
||||||
|
|
||||||
|
route
|
||||||
|
:: Proxy (NamedRoutes api)
|
||||||
|
-> Context context
|
||||||
|
-> Delayed env (api (AsServerT Handler))
|
||||||
|
-> Router env
|
||||||
|
route _ ctx delayed =
|
||||||
|
case proof @api @Handler of
|
||||||
|
Dict -> route (Proxy @(ToServantApi api)) ctx (toServant <$> delayed)
|
||||||
|
|
||||||
|
hoistServerWithContext
|
||||||
|
:: forall m n. Proxy (NamedRoutes api)
|
||||||
|
-> Proxy context
|
||||||
|
-> (forall x. m x -> n x)
|
||||||
|
-> api (AsServerT m)
|
||||||
|
-> api (AsServerT n)
|
||||||
|
hoistServerWithContext _ pctx nat server =
|
||||||
|
case (proof @api @m, proof @api @n) of
|
||||||
|
(Dict, Dict) ->
|
||||||
|
fromServant servantSrvN
|
||||||
|
where
|
||||||
|
servantSrvM :: ServerT (ToServantApi api) m =
|
||||||
|
toServant server
|
||||||
|
servantSrvN :: ServerT (ToServantApi api) n =
|
||||||
|
hoistServerWithContext (Proxy @(ToServantApi api)) pctx nat servantSrvM
|
||||||
|
|
Loading…
Reference in a new issue