{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds -fno-warn-unused-imports #-}
module Kubernetes.OpenAPI.API.AuthorizationV1 where
import Kubernetes.OpenAPI.Core
import Kubernetes.OpenAPI.MimeTypes
import Kubernetes.OpenAPI.Model as M
import qualified Data.Aeson as A
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Data as P (Typeable, TypeRep, typeOf, typeRep)
import qualified Data.Foldable as P
import qualified Data.Map as Map
import qualified Data.Maybe as P
import qualified Data.Proxy as P (Proxy(..))
import qualified Data.Set as Set
import qualified Data.String as P
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.Time as TI
import qualified Network.HTTP.Client.MultipartFormData as NH
import qualified Network.HTTP.Media as ME
import qualified Network.HTTP.Types as NH
import qualified Web.FormUrlEncoded as WH
import qualified Web.HttpApiData as WH
import Data.Text (Text)
import GHC.Base ((<|>))
import Prelude ((==),(/=),($), (.),(<$>),(<*>),(>>=),Maybe(..),Bool(..),Char,Double,FilePath,Float,Int,Integer,String,fmap,undefined,mempty,maybe,pure,Monad,Applicative,Functor)
import qualified Prelude as P
createNamespacedLocalSubjectAccessReview
:: (Consumes CreateNamespacedLocalSubjectAccessReview contentType, MimeRender contentType V1LocalSubjectAccessReview)
=> ContentType contentType
-> Accept accept
-> V1LocalSubjectAccessReview
-> Namespace
-> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType V1LocalSubjectAccessReview accept
createNamespacedLocalSubjectAccessReview :: ContentType contentType
-> Accept accept
-> V1LocalSubjectAccessReview
-> Namespace
-> KubernetesRequest
CreateNamespacedLocalSubjectAccessReview
contentType
V1LocalSubjectAccessReview
accept
createNamespacedLocalSubjectAccessReview ContentType contentType
_ Accept accept
_ V1LocalSubjectAccessReview
body (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
CreateNamespacedLocalSubjectAccessReview
contentType
V1LocalSubjectAccessReview
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/authorization.k8s.io/v1/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/localsubjectaccessreviews"]
KubernetesRequest
CreateNamespacedLocalSubjectAccessReview
contentType
V1LocalSubjectAccessReview
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateNamespacedLocalSubjectAccessReview
contentType
V1LocalSubjectAccessReview
accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
KubernetesRequest
CreateNamespacedLocalSubjectAccessReview
contentType
V1LocalSubjectAccessReview
accept
-> V1LocalSubjectAccessReview
-> KubernetesRequest
CreateNamespacedLocalSubjectAccessReview
contentType
V1LocalSubjectAccessReview
accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1LocalSubjectAccessReview
body
data CreateNamespacedLocalSubjectAccessReview
instance HasBodyParam CreateNamespacedLocalSubjectAccessReview V1LocalSubjectAccessReview
instance HasOptionalParam CreateNamespacedLocalSubjectAccessReview DryRun where
applyOptionalParam :: KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
-> DryRun
-> KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
applyOptionalParam KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
req KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam CreateNamespacedLocalSubjectAccessReview FieldManager where
applyOptionalParam :: KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
-> FieldManager
-> KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
applyOptionalParam KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
req KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam CreateNamespacedLocalSubjectAccessReview Pretty where
applyOptionalParam :: KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
-> Pretty
-> KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
applyOptionalParam KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
req KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedLocalSubjectAccessReview contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes CreateNamespacedLocalSubjectAccessReview mtype
instance Produces CreateNamespacedLocalSubjectAccessReview MimeJSON
instance Produces CreateNamespacedLocalSubjectAccessReview MimeVndKubernetesProtobuf
instance Produces CreateNamespacedLocalSubjectAccessReview MimeYaml
createSelfSubjectAccessReview
:: (Consumes CreateSelfSubjectAccessReview contentType, MimeRender contentType V1SelfSubjectAccessReview)
=> ContentType contentType
-> Accept accept
-> V1SelfSubjectAccessReview
-> KubernetesRequest CreateSelfSubjectAccessReview contentType V1SelfSubjectAccessReview accept
createSelfSubjectAccessReview :: ContentType contentType
-> Accept accept
-> V1SelfSubjectAccessReview
-> KubernetesRequest
CreateSelfSubjectAccessReview
contentType
V1SelfSubjectAccessReview
accept
createSelfSubjectAccessReview ContentType contentType
_ Accept accept
_ V1SelfSubjectAccessReview
body =
Method
-> [ByteString]
-> KubernetesRequest
CreateSelfSubjectAccessReview
contentType
V1SelfSubjectAccessReview
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/authorization.k8s.io/v1/selfsubjectaccessreviews"]
KubernetesRequest
CreateSelfSubjectAccessReview
contentType
V1SelfSubjectAccessReview
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateSelfSubjectAccessReview
contentType
V1SelfSubjectAccessReview
accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
KubernetesRequest
CreateSelfSubjectAccessReview
contentType
V1SelfSubjectAccessReview
accept
-> V1SelfSubjectAccessReview
-> KubernetesRequest
CreateSelfSubjectAccessReview
contentType
V1SelfSubjectAccessReview
accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1SelfSubjectAccessReview
body
data CreateSelfSubjectAccessReview
instance HasBodyParam CreateSelfSubjectAccessReview V1SelfSubjectAccessReview
instance HasOptionalParam CreateSelfSubjectAccessReview DryRun where
applyOptionalParam :: KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
-> DryRun
-> KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
applyOptionalParam KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
req KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam CreateSelfSubjectAccessReview FieldManager where
applyOptionalParam :: KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
-> FieldManager
-> KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
applyOptionalParam KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
req KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam CreateSelfSubjectAccessReview Pretty where
applyOptionalParam :: KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
-> Pretty
-> KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
applyOptionalParam KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
req KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateSelfSubjectAccessReview contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes CreateSelfSubjectAccessReview mtype
instance Produces CreateSelfSubjectAccessReview MimeJSON
instance Produces CreateSelfSubjectAccessReview MimeVndKubernetesProtobuf
instance Produces CreateSelfSubjectAccessReview MimeYaml
createSelfSubjectRulesReview
:: (Consumes CreateSelfSubjectRulesReview contentType, MimeRender contentType V1SelfSubjectRulesReview)
=> ContentType contentType
-> Accept accept
-> V1SelfSubjectRulesReview
-> KubernetesRequest CreateSelfSubjectRulesReview contentType V1SelfSubjectRulesReview accept
createSelfSubjectRulesReview :: ContentType contentType
-> Accept accept
-> V1SelfSubjectRulesReview
-> KubernetesRequest
CreateSelfSubjectRulesReview
contentType
V1SelfSubjectRulesReview
accept
createSelfSubjectRulesReview ContentType contentType
_ Accept accept
_ V1SelfSubjectRulesReview
body =
Method
-> [ByteString]
-> KubernetesRequest
CreateSelfSubjectRulesReview
contentType
V1SelfSubjectRulesReview
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/authorization.k8s.io/v1/selfsubjectrulesreviews"]
KubernetesRequest
CreateSelfSubjectRulesReview
contentType
V1SelfSubjectRulesReview
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateSelfSubjectRulesReview
contentType
V1SelfSubjectRulesReview
accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
KubernetesRequest
CreateSelfSubjectRulesReview
contentType
V1SelfSubjectRulesReview
accept
-> V1SelfSubjectRulesReview
-> KubernetesRequest
CreateSelfSubjectRulesReview
contentType
V1SelfSubjectRulesReview
accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1SelfSubjectRulesReview
body
data CreateSelfSubjectRulesReview
instance HasBodyParam CreateSelfSubjectRulesReview V1SelfSubjectRulesReview
instance HasOptionalParam CreateSelfSubjectRulesReview DryRun where
applyOptionalParam :: KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
-> DryRun
-> KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
applyOptionalParam KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
req KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam CreateSelfSubjectRulesReview FieldManager where
applyOptionalParam :: KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
-> FieldManager
-> KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
applyOptionalParam KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
req KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam CreateSelfSubjectRulesReview Pretty where
applyOptionalParam :: KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
-> Pretty
-> KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
applyOptionalParam KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
req KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateSelfSubjectRulesReview contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes CreateSelfSubjectRulesReview mtype
instance Produces CreateSelfSubjectRulesReview MimeJSON
instance Produces CreateSelfSubjectRulesReview MimeVndKubernetesProtobuf
instance Produces CreateSelfSubjectRulesReview MimeYaml
createSubjectAccessReview
:: (Consumes CreateSubjectAccessReview contentType, MimeRender contentType V1SubjectAccessReview)
=> ContentType contentType
-> Accept accept
-> V1SubjectAccessReview
-> KubernetesRequest CreateSubjectAccessReview contentType V1SubjectAccessReview accept
createSubjectAccessReview :: ContentType contentType
-> Accept accept
-> V1SubjectAccessReview
-> KubernetesRequest
CreateSubjectAccessReview contentType V1SubjectAccessReview accept
createSubjectAccessReview ContentType contentType
_ Accept accept
_ V1SubjectAccessReview
body =
Method
-> [ByteString]
-> KubernetesRequest
CreateSubjectAccessReview contentType V1SubjectAccessReview accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/authorization.k8s.io/v1/subjectaccessreviews"]
KubernetesRequest
CreateSubjectAccessReview contentType V1SubjectAccessReview accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateSubjectAccessReview contentType V1SubjectAccessReview accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
KubernetesRequest
CreateSubjectAccessReview contentType V1SubjectAccessReview accept
-> V1SubjectAccessReview
-> KubernetesRequest
CreateSubjectAccessReview contentType V1SubjectAccessReview accept
forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
MimeRender contentType param) =>
KubernetesRequest req contentType res accept
-> param -> KubernetesRequest req contentType res accept
`setBodyParam` V1SubjectAccessReview
body
data CreateSubjectAccessReview
instance HasBodyParam CreateSubjectAccessReview V1SubjectAccessReview
instance HasOptionalParam CreateSubjectAccessReview DryRun where
applyOptionalParam :: KubernetesRequest CreateSubjectAccessReview contentType res accept
-> DryRun
-> KubernetesRequest
CreateSubjectAccessReview contentType res accept
applyOptionalParam KubernetesRequest CreateSubjectAccessReview contentType res accept
req (DryRun Text
xs) =
KubernetesRequest CreateSubjectAccessReview contentType res accept
req KubernetesRequest CreateSubjectAccessReview contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateSubjectAccessReview contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"dryRun", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam CreateSubjectAccessReview FieldManager where
applyOptionalParam :: KubernetesRequest CreateSubjectAccessReview contentType res accept
-> FieldManager
-> KubernetesRequest
CreateSubjectAccessReview contentType res accept
applyOptionalParam KubernetesRequest CreateSubjectAccessReview contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest CreateSubjectAccessReview contentType res accept
req KubernetesRequest CreateSubjectAccessReview contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateSubjectAccessReview contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam CreateSubjectAccessReview Pretty where
applyOptionalParam :: KubernetesRequest CreateSubjectAccessReview contentType res accept
-> Pretty
-> KubernetesRequest
CreateSubjectAccessReview contentType res accept
applyOptionalParam KubernetesRequest CreateSubjectAccessReview contentType res accept
req (Pretty Text
xs) =
KubernetesRequest CreateSubjectAccessReview contentType res accept
req KubernetesRequest CreateSubjectAccessReview contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateSubjectAccessReview contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"pretty", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes CreateSubjectAccessReview mtype
instance Produces CreateSubjectAccessReview MimeJSON
instance Produces CreateSubjectAccessReview MimeVndKubernetesProtobuf
instance Produces CreateSubjectAccessReview MimeYaml
getAPIResources
:: Accept accept
-> KubernetesRequest GetAPIResources MimeNoContent V1APIResourceList accept
getAPIResources :: Accept accept
-> KubernetesRequest
GetAPIResources MimeNoContent V1APIResourceList accept
getAPIResources Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
GetAPIResources MimeNoContent V1APIResourceList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/authorization.k8s.io/v1/"]
KubernetesRequest
GetAPIResources MimeNoContent V1APIResourceList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
GetAPIResources MimeNoContent V1APIResourceList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall k (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)
data GetAPIResources
instance Produces GetAPIResources MimeJSON
instance Produces GetAPIResources MimeVndKubernetesProtobuf
instance Produces GetAPIResources MimeYaml