Prototype
This commit is contained in:
parent
c19ed0fb92
commit
6d43580208
4 changed files with 28 additions and 1 deletions
|
@ -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
|
||||||
|
|
|
@ -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
|
||||||
|
|
12
servant/src/Servant/API/RedirectOf.hs
Normal file
12
servant/src/Servant/API/RedirectOf.hs
Normal 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
|
|
@ -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)
|
||||||
|
]
|
||||||
|
|
Loading…
Reference in a new issue