{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Servant.Benchmark.HasEndpoint (HasEndpoint (..)) where
import Data.Aeson (ToJSON)
import qualified Data.Aeson as A
import qualified Data.ByteString.Lazy.Char8 as BS
import Data.Data (Proxy (..))
import Data.Kind (Type)
import Data.List (foldl')
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import GHC.TypeLits (KnownSymbol, Nat, Symbol, symbolVal)
import Servant.API hiding (contentType, contentTypes)
import Servant.Benchmark.BasicAuth (encodeBasicAuth)
import Servant.Benchmark.Endpoint (Endpoint (..), ctJSON, ctPlainText, mkHeader)
import Servant.Benchmark.Generator (Generator, (:>:) (..))
import Servant.Benchmark.ToText
import Test.QuickCheck (generate, listOf)
class HasEndpoint (api :: Type) where
getEndpoint :: Proxy api -> Generator api -> IO Endpoint
weight :: Proxy api -> Generator api -> Word
instance
forall (sym :: Symbol) (rest :: Type).
(KnownSymbol sym, HasEndpoint rest) =>
HasEndpoint (sym :> rest)
where
getEndpoint :: Proxy (sym :> rest) -> Generator (sym :> rest) -> IO Endpoint
getEndpoint Proxy (sym :> rest)
_ Generator (sym :> rest)
gen = do
Endpoint -> Endpoint -> Endpoint
forall a. Semigroup a => a -> a -> a
(<>) Endpoint
forall a. Monoid a => a
mempty{path :: Text
path = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Char
'/' Char -> String -> String
forall a. a -> [a] -> [a]
: Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy sym
forall k (t :: k). Proxy t
Proxy @sym)}
(Endpoint -> Endpoint) -> IO Endpoint -> IO Endpoint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (sym :> rest)
gen
weight :: Proxy (sym :> rest) -> Generator (sym :> rest) -> Word
weight Proxy (sym :> rest)
_ Generator (sym :> rest)
gen = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (sym :> rest)
gen
instance
forall k (method :: k) (statusCode :: Nat) (contentTypes :: [Type]) (a :: Type).
ReflectMethod method =>
HasEndpoint (Verb method statusCode contentTypes a)
where
getEndpoint :: Proxy (Verb method statusCode contentTypes a)
-> Generator (Verb method statusCode contentTypes a) -> IO Endpoint
getEndpoint Proxy (Verb method statusCode contentTypes a)
_ Generator (Verb method statusCode contentTypes a)
gen =
Endpoint -> IO Endpoint
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Endpoint -> IO Endpoint) -> Endpoint -> IO Endpoint
forall a b. (a -> b) -> a -> b
$
Endpoint
forall a. Monoid a => a
mempty
{ name :: Text
name = (Text, Word) -> Text
forall a b. (a, b) -> a
fst (Text, Word)
Generator (Verb method statusCode contentTypes a)
gen
, method :: Maybe Method
method = Method -> Maybe Method
forall a. a -> Maybe a
Just (Method -> Maybe Method) -> Method -> Maybe Method
forall a b. (a -> b) -> a -> b
$ Proxy method -> Method
forall k (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (Proxy method
forall k (t :: k). Proxy t
Proxy @method)
}
weight :: Proxy (Verb method statusCode contentTypes a)
-> Generator (Verb method statusCode contentTypes a) -> Word
weight Proxy (Verb method statusCode contentTypes a)
_ Generator (Verb method statusCode contentTypes a)
gen = (Text, Word) -> Word
forall a b. (a, b) -> b
snd (Text, Word)
Generator (Verb method statusCode contentTypes a)
gen
instance
forall (a :: Type) (rest :: Type).
(ToJSON a, HasEndpoint rest) =>
HasEndpoint (ReqBody '[JSON] a :> rest)
where
getEndpoint :: Proxy (ReqBody '[JSON] a :> rest)
-> Generator (ReqBody '[JSON] a :> rest) -> IO Endpoint
getEndpoint Proxy (ReqBody '[JSON] a :> rest)
_ (genLeft :>: genRest) = do
a
value <- Gen a -> IO a
forall a. Gen a -> IO a
generate Gen a
genLeft
Endpoint -> Endpoint -> Endpoint
forall a. Semigroup a => a -> a -> a
(<>)
Endpoint
forall a. Monoid a => a
mempty
{ body :: Maybe Method
body = Method -> Maybe Method
forall a. a -> Maybe a
Just (Method -> Maybe Method) -> Method -> Maybe Method
forall a b. (a -> b) -> a -> b
$ ByteString -> Method
BS.toStrict (ByteString -> Method) -> ByteString -> Method
forall a b. (a -> b) -> a -> b
$ a -> ByteString
forall a. ToJSON a => a -> ByteString
A.encode a
value
, contentType :: Maybe MediaType
contentType = MediaType -> Maybe MediaType
forall a. a -> Maybe a
Just MediaType
ctJSON
}
(Endpoint -> Endpoint) -> IO Endpoint -> IO Endpoint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
weight :: Proxy (ReqBody '[JSON] a :> rest)
-> Generator (ReqBody '[JSON] a :> rest) -> Word
weight Proxy (ReqBody '[JSON] a :> rest)
_ (_ :>: genRest) = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
instance
forall (a :: Type) (rest :: Type).
(ToText a, HasEndpoint rest) =>
HasEndpoint (ReqBody '[PlainText] a :> rest)
where
getEndpoint :: Proxy (ReqBody '[PlainText] a :> rest)
-> Generator (ReqBody '[PlainText] a :> rest) -> IO Endpoint
getEndpoint Proxy (ReqBody '[PlainText] a :> rest)
_ (genLeft :>: genRest) = do
a
value <- Gen a -> IO a
forall a. Gen a -> IO a
generate Gen a
genLeft
Endpoint -> Endpoint -> Endpoint
forall a. Semigroup a => a -> a -> a
(<>)
Endpoint
forall a. Monoid a => a
mempty
{ body :: Maybe Method
body = Method -> Maybe Method
forall a. a -> Maybe a
Just (Method -> Maybe Method) -> Method -> Maybe Method
forall a b. (a -> b) -> a -> b
$ Text -> Method
T.encodeUtf8 (Text -> Method) -> Text -> Method
forall a b. (a -> b) -> a -> b
$ a -> Text
forall a. ToText a => a -> Text
toText a
value
, contentType :: Maybe MediaType
contentType = MediaType -> Maybe MediaType
forall a. a -> Maybe a
Just MediaType
ctPlainText
}
(Endpoint -> Endpoint) -> IO Endpoint -> IO Endpoint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
weight :: Proxy (ReqBody '[PlainText] a :> rest)
-> Generator (ReqBody '[PlainText] a :> rest) -> Word
weight Proxy (ReqBody '[PlainText] a :> rest)
_ (_ :>: genRest) = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
instance
forall (params :: Symbol) (a :: Type) (rest :: Type).
(KnownSymbol params, ToText a, HasEndpoint rest) =>
HasEndpoint (QueryParams params a :> rest)
where
getEndpoint :: Proxy (QueryParams params a :> rest)
-> Generator (QueryParams params a :> rest) -> IO Endpoint
getEndpoint Proxy (QueryParams params a :> rest)
_ (genLeft :>: genRest) = do
let queryPath :: Text
queryPath = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Proxy params -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy params
forall k (t :: k). Proxy t
Proxy @params)
[a]
arbParams <- Gen [a] -> IO [a]
forall a. Gen a -> IO a
generate (Gen [a] -> IO [a]) -> Gen [a] -> IO [a]
forall a b. (a -> b) -> a -> b
$ Gen a -> Gen [a]
forall a. Gen a -> Gen [a]
listOf Gen a
genLeft
let queryParams :: Text
queryParams = Text -> Text
T.init (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ (Text -> a -> Text) -> Text -> [a] -> Text
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Text -> Text -> a -> Text
addParam Text
queryPath) Text
"" [a]
arbParams
Endpoint -> Endpoint -> Endpoint
forall a. Semigroup a => a -> a -> a
(<>) Endpoint
forall a. Monoid a => a
mempty{path :: Text
path = Char
'?' Char -> Text -> Text
`T.cons` Text
queryParams}
(Endpoint -> Endpoint) -> IO Endpoint -> IO Endpoint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
where
addParam :: T.Text -> T.Text -> a -> T.Text
addParam :: Text -> Text -> a -> Text
addParam Text
root Text
acc a
a =
Text
acc Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
root Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"[]=<" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. ToText a => a -> Text
toText a
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
">&"
weight :: Proxy (QueryParams params a :> rest)
-> Generator (QueryParams params a :> rest) -> Word
weight Proxy (QueryParams params a :> rest)
_ (_ :>: genRest) = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
instance
forall (sym :: Symbol) (rest :: Type).
(KnownSymbol sym, HasEndpoint rest) =>
HasEndpoint (QueryFlag sym :> rest)
where
getEndpoint :: Proxy (QueryFlag sym :> rest)
-> Generator (QueryFlag sym :> rest) -> IO Endpoint
getEndpoint Proxy (QueryFlag sym :> rest)
_ Generator (QueryFlag sym :> rest)
gen =
Endpoint -> Endpoint -> Endpoint
forall a. Semigroup a => a -> a -> a
(<>) Endpoint
forall a. Monoid a => a
mempty{path :: Text
path = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"?" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy sym
forall k (t :: k). Proxy t
Proxy @sym)}
(Endpoint -> Endpoint) -> IO Endpoint -> IO Endpoint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (QueryFlag sym :> rest)
gen
weight :: Proxy (QueryFlag sym :> rest)
-> Generator (QueryFlag sym :> rest) -> Word
weight Proxy (QueryFlag sym :> rest)
_ Generator (QueryFlag sym :> rest)
gen = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (QueryFlag sym :> rest)
gen
instance
forall (sym :: Symbol) (a :: Type) (rest :: Type).
(ToText a, HasEndpoint rest) =>
HasEndpoint (Capture sym a :> rest)
where
getEndpoint :: Proxy (Capture sym a :> rest)
-> Generator (Capture sym a :> rest) -> IO Endpoint
getEndpoint Proxy (Capture sym a :> rest)
_ (gen :>: genRest) = do
a
value <- Gen a -> IO a
forall a. Gen a -> IO a
generate Gen a
gen
Endpoint -> Endpoint -> Endpoint
forall a. Semigroup a => a -> a -> a
(<>) Endpoint
forall a. Monoid a => a
mempty{path :: Text
path = Char
'/' Char -> Text -> Text
`T.cons` a -> Text
forall a. ToText a => a -> Text
toText a
value} (Endpoint -> Endpoint) -> IO Endpoint -> IO Endpoint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
weight :: Proxy (Capture sym a :> rest)
-> Generator (Capture sym a :> rest) -> Word
weight Proxy (Capture sym a :> rest)
_ (_ :>: genRest) = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
instance
forall (sym :: Symbol) (a :: Type) (rest :: Type).
(ToText a, HasEndpoint rest) =>
HasEndpoint (CaptureAll sym a :> rest)
where
getEndpoint :: Proxy (CaptureAll sym a :> rest)
-> Generator (CaptureAll sym a :> rest) -> IO Endpoint
getEndpoint Proxy (CaptureAll sym a :> rest)
_ (gen :>: genRest) = do
a
value <- Gen a -> IO a
forall a. Gen a -> IO a
generate Gen a
gen
Endpoint -> Endpoint -> Endpoint
forall a. Semigroup a => a -> a -> a
(<>) Endpoint
forall a. Monoid a => a
mempty{path :: Text
path = Char
'/' Char -> Text -> Text
`T.cons` a -> Text
forall a. ToText a => a -> Text
toText a
value} (Endpoint -> Endpoint) -> IO Endpoint -> IO Endpoint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
weight :: Proxy (CaptureAll sym a :> rest)
-> Generator (CaptureAll sym a :> rest) -> Word
weight Proxy (CaptureAll sym a :> rest)
_ (_ :>: genRest) = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
instance
forall (sym :: Symbol) (a :: Type) (rest :: Type).
(KnownSymbol sym, ToText a, HasEndpoint rest) =>
HasEndpoint (Header sym a :> rest)
where
getEndpoint :: Proxy (Header sym a :> rest)
-> Generator (Header sym a :> rest) -> IO Endpoint
getEndpoint Proxy (Header sym a :> rest)
_ (gen :>: genRest) = do
let headerName :: Text
headerName = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy sym
forall k (t :: k). Proxy t
Proxy @sym)
a
headerValue <- Gen a -> IO a
forall a. Gen a -> IO a
generate Gen a
gen
let header :: Header
header = Text -> Text -> Header
mkHeader Text
headerName (Text -> Header) -> Text -> Header
forall a b. (a -> b) -> a -> b
$ a -> Text
forall a. ToText a => a -> Text
toText a
headerValue
Endpoint -> Endpoint -> Endpoint
forall a. Semigroup a => a -> a -> a
(<>) Endpoint
forall a. Monoid a => a
mempty{headers :: [Header]
headers = [Header
header]} (Endpoint -> Endpoint) -> IO Endpoint -> IO Endpoint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
weight :: Proxy (Header sym a :> rest)
-> Generator (Header sym a :> rest) -> Word
weight Proxy (Header sym a :> rest)
_ (_ :>: genRest) = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
instance
forall (rest :: Type).
HasEndpoint rest =>
HasEndpoint (HttpVersion :> rest)
where
getEndpoint :: Proxy (HttpVersion :> rest)
-> Generator (HttpVersion :> rest) -> IO Endpoint
getEndpoint Proxy (HttpVersion :> rest)
_ Generator (HttpVersion :> rest)
gen = Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (HttpVersion :> rest)
gen
weight :: Proxy (HttpVersion :> rest)
-> Generator (HttpVersion :> rest) -> Word
weight Proxy (HttpVersion :> rest)
_ Generator (HttpVersion :> rest)
gen = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (HttpVersion :> rest)
gen
instance HasEndpoint EmptyAPI where
getEndpoint :: Proxy EmptyAPI -> Generator EmptyAPI -> IO Endpoint
getEndpoint Proxy EmptyAPI
_ Generator EmptyAPI
gen = Endpoint -> IO Endpoint
forall (f :: * -> *) a. Applicative f => a -> f a
pure Endpoint
forall a. Monoid a => a
mempty{name :: Text
name = (Text, Word) -> Text
forall a b. (a, b) -> a
fst (Text, Word)
Generator EmptyAPI
gen}
weight :: Proxy EmptyAPI -> Generator EmptyAPI -> Word
weight Proxy EmptyAPI
_ Generator EmptyAPI
_ = Word
0
instance
forall (a :: Type) (rest :: Type).
(ToText a, HasEndpoint rest) =>
HasEndpoint (Fragment a :> rest)
where
getEndpoint :: Proxy (Fragment a :> rest)
-> Generator (Fragment a :> rest) -> IO Endpoint
getEndpoint Proxy (Fragment a :> rest)
_ (gen :>: genRest) = do
a
value <- Gen a -> IO a
forall a. Gen a -> IO a
generate Gen a
gen
Endpoint -> Endpoint -> Endpoint
forall a. Semigroup a => a -> a -> a
(<>) Endpoint
forall a. Monoid a => a
mempty{path :: Text
path = Char
'#' Char -> Text -> Text
`T.cons` a -> Text
forall a. ToText a => a -> Text
toText a
value}
(Endpoint -> Endpoint) -> IO Endpoint -> IO Endpoint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
weight :: Proxy (Fragment a :> rest)
-> Generator (Fragment a :> rest) -> Word
weight Proxy (Fragment a :> rest)
_ (_ :>: genRest) = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
instance
forall (rest :: Type).
HasEndpoint rest =>
HasEndpoint (RemoteHost :> rest)
where
getEndpoint :: Proxy (RemoteHost :> rest)
-> Generator (RemoteHost :> rest) -> IO Endpoint
getEndpoint Proxy (RemoteHost :> rest)
_ Generator (RemoteHost :> rest)
gen = Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (RemoteHost :> rest)
gen
weight :: Proxy (RemoteHost :> rest)
-> Generator (RemoteHost :> rest) -> Word
weight Proxy (RemoteHost :> rest)
_ Generator (RemoteHost :> rest)
gen = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (RemoteHost :> rest)
gen
instance
forall (rest :: Type).
HasEndpoint rest =>
HasEndpoint (IsSecure :> rest)
where
getEndpoint :: Proxy (IsSecure :> rest)
-> Generator (IsSecure :> rest) -> IO Endpoint
getEndpoint Proxy (IsSecure :> rest)
_ Generator (IsSecure :> rest)
gen = Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (IsSecure :> rest)
gen
weight :: Proxy (IsSecure :> rest) -> Generator (IsSecure :> rest) -> Word
weight Proxy (IsSecure :> rest)
_ Generator (IsSecure :> rest)
gen = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (IsSecure :> rest)
gen
instance
forall (name :: Symbol) (sub :: [Type]) (api :: Type).
HasEndpoint api =>
HasEndpoint (WithNamedContext name sub api)
where
getEndpoint :: Proxy (WithNamedContext name sub api)
-> Generator (WithNamedContext name sub api) -> IO Endpoint
getEndpoint Proxy (WithNamedContext name sub api)
_ Generator (WithNamedContext name sub api)
gen = Proxy api -> Generator api -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy api
forall k (t :: k). Proxy t
Proxy @api) Generator api
Generator (WithNamedContext name sub api)
gen
weight :: Proxy (WithNamedContext name sub api)
-> Generator (WithNamedContext name sub api) -> Word
weight Proxy (WithNamedContext name sub api)
_ Generator (WithNamedContext name sub api)
gen = Proxy api -> Generator api -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy api
forall k (t :: k). Proxy t
Proxy @api) Generator api
Generator (WithNamedContext name sub api)
gen
instance
forall (realm :: Symbol) (userData :: Type) (rest :: Type).
(HasEndpoint rest) =>
HasEndpoint (BasicAuth realm userData :> rest)
where
getEndpoint :: Proxy (BasicAuth realm userData :> rest)
-> Generator (BasicAuth realm userData :> rest) -> IO Endpoint
getEndpoint Proxy (BasicAuth realm userData :> rest)
_ (f :>: genUserData :>: genRest) = do
Header
authHeader <- (userData -> BasicAuthData) -> Gen userData -> IO Header
forall a. (a -> BasicAuthData) -> Gen a -> IO Header
encodeBasicAuth userData -> BasicAuthData
f Gen userData
genUserData
Endpoint -> Endpoint -> Endpoint
forall a. Semigroup a => a -> a -> a
(<>)
Endpoint
forall a. Monoid a => a
mempty{headers :: [Header]
headers = [Header
authHeader]}
(Endpoint -> Endpoint) -> IO Endpoint -> IO Endpoint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
weight :: Proxy (BasicAuth realm userData :> rest)
-> Generator (BasicAuth realm userData :> rest) -> Word
weight Proxy (BasicAuth realm userData :> rest)
_ (_ :>: _ :>: genRest) = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
genRest
instance
forall (sym :: Symbol) (rest :: Type).
HasEndpoint rest =>
HasEndpoint (Description sym :> rest)
where
getEndpoint :: Proxy (Description sym :> rest)
-> Generator (Description sym :> rest) -> IO Endpoint
getEndpoint Proxy (Description sym :> rest)
_ Generator (Description sym :> rest)
gen = Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (Description sym :> rest)
gen
weight :: Proxy (Description sym :> rest)
-> Generator (Description sym :> rest) -> Word
weight Proxy (Description sym :> rest)
_ Generator (Description sym :> rest)
gen = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (Description sym :> rest)
gen
instance
forall (sym :: Symbol) (rest :: Type).
HasEndpoint rest =>
HasEndpoint (Summary sym :> rest)
where
getEndpoint :: Proxy (Summary sym :> rest)
-> Generator (Summary sym :> rest) -> IO Endpoint
getEndpoint Proxy (Summary sym :> rest)
_ Generator (Summary sym :> rest)
gen = Proxy rest -> Generator rest -> IO Endpoint
forall api.
HasEndpoint api =>
Proxy api -> Generator api -> IO Endpoint
getEndpoint (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (Summary sym :> rest)
gen
weight :: Proxy (Summary sym :> rest)
-> Generator (Summary sym :> rest) -> Word
weight Proxy (Summary sym :> rest)
_ Generator (Summary sym :> rest)
gen = Proxy rest -> Generator rest -> Word
forall api. HasEndpoint api => Proxy api -> Generator api -> Word
weight (Proxy rest
forall k (t :: k). Proxy t
Proxy @rest) Generator rest
Generator (Summary sym :> rest)
gen
instance HasEndpoint Raw where
getEndpoint :: Proxy Raw -> Generator Raw -> IO Endpoint
getEndpoint Proxy Raw
_ Generator Raw
gen = Endpoint -> IO Endpoint
forall (f :: * -> *) a. Applicative f => a -> f a
pure Endpoint
forall a. Monoid a => a
mempty{name :: Text
name = (Text, Word) -> Text
forall a b. (a, b) -> a
fst (Text, Word)
Generator Raw
gen}
weight :: Proxy Raw -> Generator Raw -> Word
weight Proxy Raw
_ Generator Raw
gen = (Text, Word) -> Word
forall a b. (a, b) -> b
snd (Text, Word)
Generator Raw
gen