Compare commits

...

4 Commits

Author SHA1 Message Date
Gaël Deest 8ed061b931 Named-based selection of sub-API 2022-04-13 13:39:45 +02:00
Gaël Deest 0f82519899 Update example to redirect within NamedRoutes 2022-04-13 11:51:12 +02:00
Gaël Deest a3efe4163d Complete usage example (empty HasServer instance) 2022-04-13 11:28:11 +02:00
Gaël Deest 6d43580208 Prototype 2022-04-04 10:51:40 +02:00
8 changed files with 83 additions and 16 deletions

View File

@ -1,10 +1,13 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE PolyKinds #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
import Prelude () import Prelude ()
import Prelude.Compat import Prelude.Compat
@ -29,7 +32,7 @@ instance FromJSON Greet
instance ToJSON Greet instance ToJSON Greet
-- API specification -- API specification
type TestApi = type TestApi' =
-- GET /hello/:name?capital={true, false} returns a Greet as JSON -- GET /hello/:name?capital={true, false} returns a Greet as JSON
"hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get '[JSON] Greet "hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get '[JSON] Greet
@ -42,6 +45,11 @@ type TestApi =
:<|> NamedRoutes OtherRoutes :<|> NamedRoutes OtherRoutes
type TestApi =
TestApi'
:<|> "redirect" :> Capture "redirectValue" Int :> RedirectOf TestApi'
data OtherRoutes mode = OtherRoutes data OtherRoutes mode = OtherRoutes
{ version :: mode :- Get '[JSON] Int { version :: mode :- Get '[JSON] Int
, bye :: mode :- "bye" :> Capture "name" Text :> Get '[JSON] Text , bye :: mode :- "bye" :> Capture "name" Text :> Get '[JSON] Text
@ -58,7 +66,7 @@ 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 :<|> otherRoutes server = (helloH :<|> postGreetH :<|> deleteGreetH :<|> otherRoutes) :<|> redirect
where otherRoutes = OtherRoutes {..} where otherRoutes = OtherRoutes {..}
bye name = pure $ "Bye, " <> name <> " !" bye name = pure $ "Bye, " <> name <> " !"
@ -72,6 +80,14 @@ server = helloH :<|> postGreetH :<|> deleteGreetH :<|> otherRoutes
deleteGreetH _ = return NoContent deleteGreetH _ = return NoContent
redirect 42 = pure $
RedirectOf (Proxy @("hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get '[JSON] Greet))
(\buildPath -> buildPath "Nicolas" (Just True))
redirect _ = pure $
RedirectOf (namedRoute @"bye" @OtherRoutes)
(\buildPath -> buildPath "Gaël")
-- Turn the server into a WAI app. 'serve' is provided by servant, -- Turn the server into a WAI app. 'serve' is provided by servant,
-- more precisely by the Servant.Server module. -- more precisely by the Servant.Server module.
test :: Application test :: Application

View File

@ -76,7 +76,7 @@ import Servant.API
QueryParam', QueryParams, Raw, ReflectMethod (reflectMethod), QueryParam', QueryParams, Raw, ReflectMethod (reflectMethod),
RemoteHost, ReqBody', SBool (..), SBoolI (..), SourceIO, RemoteHost, ReqBody', SBool (..), SBoolI (..), SourceIO,
Stream, StreamBody', Summary, ToSourceIO (..), Vault, Verb, Stream, StreamBody', Summary, ToSourceIO (..), Vault, Verb,
WithNamedContext, NamedRoutes) WithNamedContext, NamedRoutes, RedirectOf(..))
import Servant.API.Generic (GenericMode(..), ToServant, ToServantApi, GServantProduct, toServant, fromServant) import Servant.API.Generic (GenericMode(..), ToServant, ToServantApi, GServantProduct, toServant, fromServant)
import Servant.API.ContentTypes import Servant.API.ContentTypes
(AcceptHeader (..), AllCTRender (..), AllCTUnrender (..), (AcceptHeader (..), AllCTRender (..), AllCTUnrender (..),
@ -888,6 +888,11 @@ instance (AtLeastOneFragment api, FragmentUnique (Fragment a1 :> api), HasServer
hoistServerWithContext _ = hoistServerWithContext (Proxy :: Proxy api) hoistServerWithContext _ = hoistServerWithContext (Proxy :: Proxy api)
instance HasServer (RedirectOf api) context where
type ServerT (RedirectOf api) m = m (RedirectOf api)
route _ = undefined
hoistServerWithContext _ _ _ = undefined
-- $setup -- $setup
-- >>> import Servant -- >>> import Servant

View File

@ -50,6 +50,7 @@ library
Servant.API.QueryParam Servant.API.QueryParam
Servant.API.Raw Servant.API.Raw
Servant.API.RemoteHost Servant.API.RemoteHost
Servant.API.RedirectOf
Servant.API.ReqBody Servant.API.ReqBody
Servant.API.ResponseHeaders Servant.API.ResponseHeaders
Servant.API.Status Servant.API.Status

View File

@ -57,6 +57,9 @@ module Servant.API (
-- * Response Headers -- * Response Headers
module Servant.API.ResponseHeaders, module Servant.API.ResponseHeaders,
-- * Redirections
module Servant.API.RedirectOf,
-- * Untyped endpoints -- * Untyped endpoints
module Servant.API.Raw, module Servant.API.Raw,
-- | Plugging in a wai 'Network.Wai.Application', serving directories -- | Plugging in a wai 'Network.Wai.Application', serving directories
@ -118,6 +121,8 @@ import Servant.API.Raw
(Raw) (Raw)
import Servant.API.RemoteHost import Servant.API.RemoteHost
(RemoteHost) (RemoteHost)
import Servant.API.RedirectOf
(RedirectOf(..))
import Servant.API.ReqBody import Servant.API.ReqBody
(ReqBody, ReqBody') (ReqBody, ReqBody')
import Servant.API.ResponseHeaders import Servant.API.ResponseHeaders
@ -138,7 +143,7 @@ import Servant.API.UVerb
import Servant.API.Vault import Servant.API.Vault
(Vault) (Vault)
import Servant.API.NamedRoutes import Servant.API.NamedRoutes
(NamedRoutes) (NamedRoutes, namedRoute)
import Servant.API.Verbs import Servant.API.Verbs
(Delete, DeleteAccepted, DeleteNoContent, (Delete, DeleteAccepted, DeleteNoContent,
DeleteNonAuthoritative, Get, GetAccepted, GetNoContent, DeleteNonAuthoritative, Get, GetAccepted, GetNoContent,

View File

@ -1,10 +1,28 @@
{-# LANGUAGE KindSignatures #-} {-# LANGUAGE AllowAmbiguousTypes #-}
{-# OPTIONS_HADDOCK not-home #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.NamedRoutes ( module Servant.API.NamedRoutes (
-- * NamedRoutes combinator -- * NamedRoutes combinator
NamedRoutes NamedRoutes
-- * Term-level helpers
, namedRoute
) where ) where
import Data.Proxy (Proxy(..))
import GHC.Records (HasField)
import GHC.TypeLits (Symbol)
import Servant.API.Generic (AsApi)
namedRoute
:: forall (field :: Symbol) (api :: * -> *) a.
HasField field (api AsApi) a
=> Proxy a
namedRoute = Proxy
-- | Combinator for embedding a record of named routes into a Servant API type. -- | Combinator for embedding a record of named routes into a Servant API type.
data NamedRoutes (api :: * -> *) data NamedRoutes (api :: * -> *)

View File

@ -0,0 +1,12 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
module Servant.API.RedirectOf where
import Data.Proxy (Proxy(..))
import Servant.Links
data RedirectOf api where
RedirectOf
:: (IsElem endpoint api, HasLink endpoint)
=> Proxy endpoint -> (forall a. MkLink endpoint a -> a) -> RedirectOf api

View File

@ -60,6 +60,8 @@ import Servant.API.Capture
import Servant.API.Fragment import Servant.API.Fragment
import Servant.API.Header import Servant.API.Header
(Header) (Header)
import Servant.API.NamedRoutes (NamedRoutes)
import Servant.API.Generic (ToServantApi)
import Servant.API.QueryParam import Servant.API.QueryParam
(QueryFlag, QueryParam, QueryParams) (QueryFlag, QueryParam, QueryParams)
import Servant.API.ReqBody import Servant.API.ReqBody
@ -73,8 +75,6 @@ import Servant.API.UVerb
import GHC.TypeLits import GHC.TypeLits
(ErrorMessage (..), TypeError) (ErrorMessage (..), TypeError)
-- * API predicates -- * API predicates
-- | Flatten API into a list of endpoints. -- | Flatten API into a list of endpoints.
@ -127,6 +127,7 @@ type family IsElem' a s :: Constraint
-- request represented by @a@ matches the endpoints serving @b@ (for the -- request represented by @a@ matches the endpoints serving @b@ (for the
-- latter, use 'IsIn'). -- latter, use 'IsIn').
type family IsElem endpoint api :: Constraint where type family IsElem endpoint api :: Constraint where
IsElem endpoint (NamedRoutes rec) = IsElem endpoint (ToServantApi rec)
IsElem e (sa :<|> sb) = Or (IsElem e sa) (IsElem e sb) IsElem e (sa :<|> sb) = Or (IsElem e sa) (IsElem e sb)
IsElem (e :> sa) (e :> sb) = IsElem sa sb IsElem (e :> sa) (e :> sb) = IsElem sa sb
IsElem sa (Header sym x :> sb) = IsElem sa sb IsElem sa (Header sym x :> sb) = IsElem sa sb

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
-- | This is a module containing an API with all `Servant.API` combinators. It -- | This is a module containing an API with all `Servant.API` combinators. It
@ -44,11 +45,13 @@ type ComprehensiveAPIWithoutStreaming =
comprehensiveAPIWithoutStreaming :: Proxy ComprehensiveAPIWithoutStreaming comprehensiveAPIWithoutStreaming :: Proxy ComprehensiveAPIWithoutStreaming
comprehensiveAPIWithoutStreaming = Proxy comprehensiveAPIWithoutStreaming = Proxy
type CaptureEndpoint = Capture' '[Description "example description"] "bar" Int :> GET
-- | @:: API -> API@, so we have linear structure of the API. -- | @:: API -> API@, so we have linear structure of the API.
type ComprehensiveAPIWithoutStreamingOrRaw' endpoint = type ComprehensiveAPIWithoutStreamingOrRaw' endpoint =
GET GET
:<|> "get-int" :> Get '[JSON] Int :<|> "get-int" :> Get '[JSON] Int
:<|> "capture" :> Capture' '[Description "example description"] "bar" Int :> GET :<|> CaptureEndpoint
:<|> "capture-lenient" :> Capture' '[Lenient] "foo" Int :> GET :<|> "capture-lenient" :> Capture' '[Lenient] "foo" Int :> GET
:<|> "header" :> Header "foo" Int :> GET :<|> "header" :> Header "foo" Int :> GET
:<|> "header-lenient" :> Header' '[Required, Lenient] "bar" Int :> GET :<|> "header-lenient" :> Header' '[Required, Lenient] "bar" Int :> GET
@ -78,3 +81,9 @@ type ComprehensiveAPIWithoutStreamingOrRaw = ComprehensiveAPIWithoutStreamingOrR
comprehensiveAPIWithoutStreamingOrRaw :: Proxy ComprehensiveAPIWithoutStreamingOrRaw comprehensiveAPIWithoutStreamingOrRaw :: Proxy ComprehensiveAPIWithoutStreamingOrRaw
comprehensiveAPIWithoutStreamingOrRaw = Proxy comprehensiveAPIWithoutStreamingOrRaw = Proxy
redirectEndpoints :: [RedirectOf ComprehensiveAPI]
redirectEndpoints =
[ RedirectOf (Proxy @GET) id
, RedirectOf (Proxy @CaptureEndpoint) (\mkLink -> mkLink 42)
]