Prototype

This commit is contained in:
Gaël Deest 2022-04-04 10:51:24 +02:00
parent c19ed0fb92
commit 6d43580208
4 changed files with 28 additions and 1 deletions

View File

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

View File

@ -57,6 +57,9 @@ module Servant.API (
-- * Response Headers
module Servant.API.ResponseHeaders,
-- * Redirections
module Servant.API.RedirectOf,
-- * Untyped endpoints
module Servant.API.Raw,
-- | Plugging in a wai 'Network.Wai.Application', serving directories
@ -118,6 +121,8 @@ import Servant.API.Raw
(Raw)
import Servant.API.RemoteHost
(RemoteHost)
import Servant.API.RedirectOf
(RedirectOf(..))
import Servant.API.ReqBody
(ReqBody, ReqBody')
import Servant.API.ResponseHeaders

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

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