{-# 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.AppsV1beta2 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
createNamespacedControllerRevision
:: (Consumes CreateNamespacedControllerRevision contentType, MimeRender contentType V1beta2ControllerRevision)
=> ContentType contentType
-> Accept accept
-> V1beta2ControllerRevision
-> Namespace
-> KubernetesRequest CreateNamespacedControllerRevision contentType V1beta2ControllerRevision accept
createNamespacedControllerRevision :: ContentType contentType
-> Accept accept
-> V1beta2ControllerRevision
-> Namespace
-> KubernetesRequest
CreateNamespacedControllerRevision
contentType
V1beta2ControllerRevision
accept
createNamespacedControllerRevision ContentType contentType
_ Accept accept
_ V1beta2ControllerRevision
body (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
CreateNamespacedControllerRevision
contentType
V1beta2ControllerRevision
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/controllerrevisions"]
KubernetesRequest
CreateNamespacedControllerRevision
contentType
V1beta2ControllerRevision
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateNamespacedControllerRevision
contentType
V1beta2ControllerRevision
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
CreateNamespacedControllerRevision
contentType
V1beta2ControllerRevision
accept
-> V1beta2ControllerRevision
-> KubernetesRequest
CreateNamespacedControllerRevision
contentType
V1beta2ControllerRevision
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` V1beta2ControllerRevision
body
data CreateNamespacedControllerRevision
instance HasBodyParam CreateNamespacedControllerRevision V1beta2ControllerRevision
instance HasOptionalParam CreateNamespacedControllerRevision Pretty where
applyOptionalParam :: KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
-> Pretty
-> KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
req KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedControllerRevision 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 HasOptionalParam CreateNamespacedControllerRevision DryRun where
applyOptionalParam :: KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
-> DryRun
-> KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
req KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedControllerRevision 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 CreateNamespacedControllerRevision FieldManager where
applyOptionalParam :: KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
-> FieldManager
-> KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
req KubernetesRequest
CreateNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedControllerRevision 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 MimeType mtype => Consumes CreateNamespacedControllerRevision mtype
instance Produces CreateNamespacedControllerRevision MimeJSON
instance Produces CreateNamespacedControllerRevision MimeVndKubernetesProtobuf
instance Produces CreateNamespacedControllerRevision MimeYaml
createNamespacedDaemonSet
:: (Consumes CreateNamespacedDaemonSet contentType, MimeRender contentType V1beta2DaemonSet)
=> ContentType contentType
-> Accept accept
-> V1beta2DaemonSet
-> Namespace
-> KubernetesRequest CreateNamespacedDaemonSet contentType V1beta2DaemonSet accept
createNamespacedDaemonSet :: ContentType contentType
-> Accept accept
-> V1beta2DaemonSet
-> Namespace
-> KubernetesRequest
CreateNamespacedDaemonSet contentType V1beta2DaemonSet accept
createNamespacedDaemonSet ContentType contentType
_ Accept accept
_ V1beta2DaemonSet
body (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
CreateNamespacedDaemonSet contentType V1beta2DaemonSet accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/daemonsets"]
KubernetesRequest
CreateNamespacedDaemonSet contentType V1beta2DaemonSet accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateNamespacedDaemonSet contentType V1beta2DaemonSet 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
CreateNamespacedDaemonSet contentType V1beta2DaemonSet accept
-> V1beta2DaemonSet
-> KubernetesRequest
CreateNamespacedDaemonSet contentType V1beta2DaemonSet 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` V1beta2DaemonSet
body
data CreateNamespacedDaemonSet
instance HasBodyParam CreateNamespacedDaemonSet V1beta2DaemonSet
instance HasOptionalParam CreateNamespacedDaemonSet Pretty where
applyOptionalParam :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept
-> Pretty
-> KubernetesRequest
CreateNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedDaemonSet contentType res accept
req (Pretty Text
xs) =
KubernetesRequest CreateNamespacedDaemonSet contentType res accept
req KubernetesRequest CreateNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedDaemonSet 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 HasOptionalParam CreateNamespacedDaemonSet DryRun where
applyOptionalParam :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept
-> DryRun
-> KubernetesRequest
CreateNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedDaemonSet contentType res accept
req (DryRun Text
xs) =
KubernetesRequest CreateNamespacedDaemonSet contentType res accept
req KubernetesRequest CreateNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedDaemonSet 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 CreateNamespacedDaemonSet FieldManager where
applyOptionalParam :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept
-> FieldManager
-> KubernetesRequest
CreateNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedDaemonSet contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest CreateNamespacedDaemonSet contentType res accept
req KubernetesRequest CreateNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedDaemonSet 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 MimeType mtype => Consumes CreateNamespacedDaemonSet mtype
instance Produces CreateNamespacedDaemonSet MimeJSON
instance Produces CreateNamespacedDaemonSet MimeVndKubernetesProtobuf
instance Produces CreateNamespacedDaemonSet MimeYaml
createNamespacedDeployment
:: (Consumes CreateNamespacedDeployment contentType, MimeRender contentType V1beta2Deployment)
=> ContentType contentType
-> Accept accept
-> V1beta2Deployment
-> Namespace
-> KubernetesRequest CreateNamespacedDeployment contentType V1beta2Deployment accept
createNamespacedDeployment :: ContentType contentType
-> Accept accept
-> V1beta2Deployment
-> Namespace
-> KubernetesRequest
CreateNamespacedDeployment contentType V1beta2Deployment accept
createNamespacedDeployment ContentType contentType
_ Accept accept
_ V1beta2Deployment
body (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
CreateNamespacedDeployment contentType V1beta2Deployment accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/deployments"]
KubernetesRequest
CreateNamespacedDeployment contentType V1beta2Deployment accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateNamespacedDeployment contentType V1beta2Deployment 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
CreateNamespacedDeployment contentType V1beta2Deployment accept
-> V1beta2Deployment
-> KubernetesRequest
CreateNamespacedDeployment contentType V1beta2Deployment 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` V1beta2Deployment
body
data CreateNamespacedDeployment
instance HasBodyParam CreateNamespacedDeployment V1beta2Deployment
instance HasOptionalParam CreateNamespacedDeployment Pretty where
applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept
-> Pretty
-> KubernetesRequest
CreateNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedDeployment contentType res accept
req (Pretty Text
xs) =
KubernetesRequest CreateNamespacedDeployment contentType res accept
req KubernetesRequest CreateNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedDeployment 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 HasOptionalParam CreateNamespacedDeployment DryRun where
applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept
-> DryRun
-> KubernetesRequest
CreateNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedDeployment contentType res accept
req (DryRun Text
xs) =
KubernetesRequest CreateNamespacedDeployment contentType res accept
req KubernetesRequest CreateNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedDeployment 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 CreateNamespacedDeployment FieldManager where
applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept
-> FieldManager
-> KubernetesRequest
CreateNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedDeployment contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest CreateNamespacedDeployment contentType res accept
req KubernetesRequest CreateNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedDeployment 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 MimeType mtype => Consumes CreateNamespacedDeployment mtype
instance Produces CreateNamespacedDeployment MimeJSON
instance Produces CreateNamespacedDeployment MimeVndKubernetesProtobuf
instance Produces CreateNamespacedDeployment MimeYaml
createNamespacedReplicaSet
:: (Consumes CreateNamespacedReplicaSet contentType, MimeRender contentType V1beta2ReplicaSet)
=> ContentType contentType
-> Accept accept
-> V1beta2ReplicaSet
-> Namespace
-> KubernetesRequest CreateNamespacedReplicaSet contentType V1beta2ReplicaSet accept
createNamespacedReplicaSet :: ContentType contentType
-> Accept accept
-> V1beta2ReplicaSet
-> Namespace
-> KubernetesRequest
CreateNamespacedReplicaSet contentType V1beta2ReplicaSet accept
createNamespacedReplicaSet ContentType contentType
_ Accept accept
_ V1beta2ReplicaSet
body (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
CreateNamespacedReplicaSet contentType V1beta2ReplicaSet accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicasets"]
KubernetesRequest
CreateNamespacedReplicaSet contentType V1beta2ReplicaSet accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateNamespacedReplicaSet contentType V1beta2ReplicaSet 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
CreateNamespacedReplicaSet contentType V1beta2ReplicaSet accept
-> V1beta2ReplicaSet
-> KubernetesRequest
CreateNamespacedReplicaSet contentType V1beta2ReplicaSet 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` V1beta2ReplicaSet
body
data CreateNamespacedReplicaSet
instance HasBodyParam CreateNamespacedReplicaSet V1beta2ReplicaSet
instance HasOptionalParam CreateNamespacedReplicaSet Pretty where
applyOptionalParam :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept
-> Pretty
-> KubernetesRequest
CreateNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedReplicaSet contentType res accept
req (Pretty Text
xs) =
KubernetesRequest CreateNamespacedReplicaSet contentType res accept
req KubernetesRequest CreateNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedReplicaSet 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 HasOptionalParam CreateNamespacedReplicaSet DryRun where
applyOptionalParam :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept
-> DryRun
-> KubernetesRequest
CreateNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedReplicaSet contentType res accept
req (DryRun Text
xs) =
KubernetesRequest CreateNamespacedReplicaSet contentType res accept
req KubernetesRequest CreateNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedReplicaSet 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 CreateNamespacedReplicaSet FieldManager where
applyOptionalParam :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept
-> FieldManager
-> KubernetesRequest
CreateNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest CreateNamespacedReplicaSet contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest CreateNamespacedReplicaSet contentType res accept
req KubernetesRequest CreateNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedReplicaSet 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 MimeType mtype => Consumes CreateNamespacedReplicaSet mtype
instance Produces CreateNamespacedReplicaSet MimeJSON
instance Produces CreateNamespacedReplicaSet MimeVndKubernetesProtobuf
instance Produces CreateNamespacedReplicaSet MimeYaml
createNamespacedStatefulSet
:: (Consumes CreateNamespacedStatefulSet contentType, MimeRender contentType V1beta2StatefulSet)
=> ContentType contentType
-> Accept accept
-> V1beta2StatefulSet
-> Namespace
-> KubernetesRequest CreateNamespacedStatefulSet contentType V1beta2StatefulSet accept
createNamespacedStatefulSet :: ContentType contentType
-> Accept accept
-> V1beta2StatefulSet
-> Namespace
-> KubernetesRequest
CreateNamespacedStatefulSet contentType V1beta2StatefulSet accept
createNamespacedStatefulSet ContentType contentType
_ Accept accept
_ V1beta2StatefulSet
body (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
CreateNamespacedStatefulSet contentType V1beta2StatefulSet accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/statefulsets"]
KubernetesRequest
CreateNamespacedStatefulSet contentType V1beta2StatefulSet accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateNamespacedStatefulSet contentType V1beta2StatefulSet 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
CreateNamespacedStatefulSet contentType V1beta2StatefulSet accept
-> V1beta2StatefulSet
-> KubernetesRequest
CreateNamespacedStatefulSet contentType V1beta2StatefulSet 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` V1beta2StatefulSet
body
data CreateNamespacedStatefulSet
instance HasBodyParam CreateNamespacedStatefulSet V1beta2StatefulSet
instance HasOptionalParam CreateNamespacedStatefulSet Pretty where
applyOptionalParam :: KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
-> Pretty
-> KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
req KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedStatefulSet 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 HasOptionalParam CreateNamespacedStatefulSet DryRun where
applyOptionalParam :: KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
-> DryRun
-> KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
req KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedStatefulSet 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 CreateNamespacedStatefulSet FieldManager where
applyOptionalParam :: KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
-> FieldManager
-> KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
req KubernetesRequest
CreateNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedStatefulSet 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 MimeType mtype => Consumes CreateNamespacedStatefulSet mtype
instance Produces CreateNamespacedStatefulSet MimeJSON
instance Produces CreateNamespacedStatefulSet MimeVndKubernetesProtobuf
instance Produces CreateNamespacedStatefulSet MimeYaml
deleteCollectionNamespacedControllerRevision
:: (Consumes DeleteCollectionNamespacedControllerRevision contentType)
=> ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType V1Status accept
deleteCollectionNamespacedControllerRevision :: ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision
contentType
V1Status
accept
deleteCollectionNamespacedControllerRevision ContentType contentType
_ Accept accept
_ (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision
contentType
V1Status
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/controllerrevisions"]
KubernetesRequest
DeleteCollectionNamespacedControllerRevision
contentType
V1Status
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision
contentType
V1Status
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 DeleteCollectionNamespacedControllerRevision
instance HasBodyParam DeleteCollectionNamespacedControllerRevision V1DeleteOptions
instance HasOptionalParam DeleteCollectionNamespacedControllerRevision Pretty where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> Pretty
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision 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 HasOptionalParam DeleteCollectionNamespacedControllerRevision Continue where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> Continue
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req (Continue Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedControllerRevision DryRun where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> DryRun
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision 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 DeleteCollectionNamespacedControllerRevision FieldSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> FieldSelector
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedControllerRevision GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteCollectionNamespacedControllerRevision LabelSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> LabelSelector
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedControllerRevision Limit where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> Limit
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req (Limit Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteCollectionNamespacedControllerRevision OrphanDependents where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam DeleteCollectionNamespacedControllerRevision PropagationPolicy where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision 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
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedControllerRevision ResourceVersion where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> ResourceVersion
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedControllerRevision TimeoutSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedControllerRevision contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance MimeType mtype => Consumes DeleteCollectionNamespacedControllerRevision mtype
instance Produces DeleteCollectionNamespacedControllerRevision MimeJSON
instance Produces DeleteCollectionNamespacedControllerRevision MimeVndKubernetesProtobuf
instance Produces DeleteCollectionNamespacedControllerRevision MimeYaml
deleteCollectionNamespacedDaemonSet
:: (Consumes DeleteCollectionNamespacedDaemonSet contentType)
=> ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType V1Status accept
deleteCollectionNamespacedDaemonSet :: ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType V1Status accept
deleteCollectionNamespacedDaemonSet ContentType contentType
_ Accept accept
_ (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/daemonsets"]
KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType V1Status 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 DeleteCollectionNamespacedDaemonSet
instance HasBodyParam DeleteCollectionNamespacedDaemonSet V1DeleteOptions
instance HasOptionalParam DeleteCollectionNamespacedDaemonSet Pretty where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> Pretty
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet 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 HasOptionalParam DeleteCollectionNamespacedDaemonSet Continue where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> Continue
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req (Continue Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedDaemonSet DryRun where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> DryRun
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet 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 DeleteCollectionNamespacedDaemonSet FieldSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> FieldSelector
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedDaemonSet GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteCollectionNamespacedDaemonSet LabelSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> LabelSelector
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedDaemonSet Limit where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> Limit
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req (Limit Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteCollectionNamespacedDaemonSet OrphanDependents where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam DeleteCollectionNamespacedDaemonSet PropagationPolicy where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet 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
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedDaemonSet ResourceVersion where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> ResourceVersion
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedDaemonSet TimeoutSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDaemonSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance MimeType mtype => Consumes DeleteCollectionNamespacedDaemonSet mtype
instance Produces DeleteCollectionNamespacedDaemonSet MimeJSON
instance Produces DeleteCollectionNamespacedDaemonSet MimeVndKubernetesProtobuf
instance Produces DeleteCollectionNamespacedDaemonSet MimeYaml
deleteCollectionNamespacedDeployment
:: (Consumes DeleteCollectionNamespacedDeployment contentType)
=> ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest DeleteCollectionNamespacedDeployment contentType V1Status accept
deleteCollectionNamespacedDeployment :: ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType V1Status accept
deleteCollectionNamespacedDeployment ContentType contentType
_ Accept accept
_ (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/deployments"]
KubernetesRequest
DeleteCollectionNamespacedDeployment contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType V1Status 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 DeleteCollectionNamespacedDeployment
instance HasBodyParam DeleteCollectionNamespacedDeployment V1DeleteOptions
instance HasOptionalParam DeleteCollectionNamespacedDeployment Pretty where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> Pretty
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDeployment 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 HasOptionalParam DeleteCollectionNamespacedDeployment Continue where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> Continue
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req (Continue Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDeployment 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedDeployment DryRun where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> DryRun
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDeployment 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 DeleteCollectionNamespacedDeployment FieldSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> FieldSelector
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDeployment 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedDeployment GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteCollectionNamespacedDeployment LabelSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> LabelSelector
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDeployment 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedDeployment Limit where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> Limit
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req (Limit Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteCollectionNamespacedDeployment OrphanDependents where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam DeleteCollectionNamespacedDeployment PropagationPolicy where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDeployment 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
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedDeployment ResourceVersion where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> ResourceVersion
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDeployment 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedDeployment TimeoutSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedDeployment contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance MimeType mtype => Consumes DeleteCollectionNamespacedDeployment mtype
instance Produces DeleteCollectionNamespacedDeployment MimeJSON
instance Produces DeleteCollectionNamespacedDeployment MimeVndKubernetesProtobuf
instance Produces DeleteCollectionNamespacedDeployment MimeYaml
deleteCollectionNamespacedReplicaSet
:: (Consumes DeleteCollectionNamespacedReplicaSet contentType)
=> ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType V1Status accept
deleteCollectionNamespacedReplicaSet :: ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType V1Status accept
deleteCollectionNamespacedReplicaSet ContentType contentType
_ Accept accept
_ (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicasets"]
KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType V1Status 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 DeleteCollectionNamespacedReplicaSet
instance HasBodyParam DeleteCollectionNamespacedReplicaSet V1DeleteOptions
instance HasOptionalParam DeleteCollectionNamespacedReplicaSet Pretty where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> Pretty
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet 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 HasOptionalParam DeleteCollectionNamespacedReplicaSet Continue where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> Continue
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req (Continue Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedReplicaSet DryRun where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> DryRun
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet 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 DeleteCollectionNamespacedReplicaSet FieldSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> FieldSelector
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedReplicaSet GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteCollectionNamespacedReplicaSet LabelSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> LabelSelector
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedReplicaSet Limit where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> Limit
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req (Limit Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteCollectionNamespacedReplicaSet OrphanDependents where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam DeleteCollectionNamespacedReplicaSet PropagationPolicy where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet 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
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedReplicaSet ResourceVersion where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> ResourceVersion
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedReplicaSet TimeoutSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedReplicaSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance MimeType mtype => Consumes DeleteCollectionNamespacedReplicaSet mtype
instance Produces DeleteCollectionNamespacedReplicaSet MimeJSON
instance Produces DeleteCollectionNamespacedReplicaSet MimeVndKubernetesProtobuf
instance Produces DeleteCollectionNamespacedReplicaSet MimeYaml
deleteCollectionNamespacedStatefulSet
:: (Consumes DeleteCollectionNamespacedStatefulSet contentType)
=> ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType V1Status accept
deleteCollectionNamespacedStatefulSet :: ContentType contentType
-> Accept accept
-> Namespace
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType V1Status accept
deleteCollectionNamespacedStatefulSet ContentType contentType
_ Accept accept
_ (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/statefulsets"]
KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType V1Status 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 DeleteCollectionNamespacedStatefulSet
instance HasBodyParam DeleteCollectionNamespacedStatefulSet V1DeleteOptions
instance HasOptionalParam DeleteCollectionNamespacedStatefulSet Pretty where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> Pretty
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet 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 HasOptionalParam DeleteCollectionNamespacedStatefulSet Continue where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> Continue
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req (Continue Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedStatefulSet DryRun where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> DryRun
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet 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 DeleteCollectionNamespacedStatefulSet FieldSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> FieldSelector
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedStatefulSet GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteCollectionNamespacedStatefulSet LabelSelector where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> LabelSelector
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedStatefulSet Limit where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> Limit
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req (Limit Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteCollectionNamespacedStatefulSet OrphanDependents where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam DeleteCollectionNamespacedStatefulSet PropagationPolicy where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet 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
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedStatefulSet ResourceVersion where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> ResourceVersion
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam DeleteCollectionNamespacedStatefulSet TimeoutSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedStatefulSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance MimeType mtype => Consumes DeleteCollectionNamespacedStatefulSet mtype
instance Produces DeleteCollectionNamespacedStatefulSet MimeJSON
instance Produces DeleteCollectionNamespacedStatefulSet MimeVndKubernetesProtobuf
instance Produces DeleteCollectionNamespacedStatefulSet MimeYaml
deleteNamespacedControllerRevision
:: (Consumes DeleteNamespacedControllerRevision contentType)
=> ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest DeleteNamespacedControllerRevision contentType V1Status accept
deleteNamespacedControllerRevision :: ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
DeleteNamespacedControllerRevision contentType V1Status accept
deleteNamespacedControllerRevision ContentType contentType
_ Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteNamespacedControllerRevision contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/controllerrevisions/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
DeleteNamespacedControllerRevision contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteNamespacedControllerRevision contentType V1Status 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 DeleteNamespacedControllerRevision
instance HasBodyParam DeleteNamespacedControllerRevision V1DeleteOptions
instance HasOptionalParam DeleteNamespacedControllerRevision Pretty where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
-> Pretty
-> KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedControllerRevision 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 HasOptionalParam DeleteNamespacedControllerRevision DryRun where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
-> DryRun
-> KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedControllerRevision 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 DeleteNamespacedControllerRevision GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteNamespacedControllerRevision OrphanDependents where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam DeleteNamespacedControllerRevision PropagationPolicy where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
req KubernetesRequest
DeleteNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedControllerRevision 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
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes DeleteNamespacedControllerRevision mtype
instance Produces DeleteNamespacedControllerRevision MimeJSON
instance Produces DeleteNamespacedControllerRevision MimeVndKubernetesProtobuf
instance Produces DeleteNamespacedControllerRevision MimeYaml
deleteNamespacedDaemonSet
:: (Consumes DeleteNamespacedDaemonSet contentType)
=> ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest DeleteNamespacedDaemonSet contentType V1Status accept
deleteNamespacedDaemonSet :: ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
DeleteNamespacedDaemonSet contentType V1Status accept
deleteNamespacedDaemonSet ContentType contentType
_ Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteNamespacedDaemonSet contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/daemonsets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
DeleteNamespacedDaemonSet contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteNamespacedDaemonSet contentType V1Status 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 DeleteNamespacedDaemonSet
instance HasBodyParam DeleteNamespacedDaemonSet V1DeleteOptions
instance HasOptionalParam DeleteNamespacedDaemonSet Pretty where
applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
-> Pretty
-> KubernetesRequest
DeleteNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
req (Pretty Text
xs) =
KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
req KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedDaemonSet 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 HasOptionalParam DeleteNamespacedDaemonSet DryRun where
applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
-> DryRun
-> KubernetesRequest
DeleteNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
req (DryRun Text
xs) =
KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
req KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedDaemonSet 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 DeleteNamespacedDaemonSet GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
req KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedDaemonSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteNamespacedDaemonSet OrphanDependents where
applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
req KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedDaemonSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam DeleteNamespacedDaemonSet PropagationPolicy where
applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
req KubernetesRequest DeleteNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedDaemonSet 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
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes DeleteNamespacedDaemonSet mtype
instance Produces DeleteNamespacedDaemonSet MimeJSON
instance Produces DeleteNamespacedDaemonSet MimeVndKubernetesProtobuf
instance Produces DeleteNamespacedDaemonSet MimeYaml
deleteNamespacedDeployment
:: (Consumes DeleteNamespacedDeployment contentType)
=> ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest DeleteNamespacedDeployment contentType V1Status accept
deleteNamespacedDeployment :: ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
DeleteNamespacedDeployment contentType V1Status accept
deleteNamespacedDeployment ContentType contentType
_ Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteNamespacedDeployment contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/deployments/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
DeleteNamespacedDeployment contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteNamespacedDeployment contentType V1Status 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 DeleteNamespacedDeployment
instance HasBodyParam DeleteNamespacedDeployment V1DeleteOptions
instance HasOptionalParam DeleteNamespacedDeployment Pretty where
applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept
-> Pretty
-> KubernetesRequest
DeleteNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedDeployment contentType res accept
req (Pretty Text
xs) =
KubernetesRequest DeleteNamespacedDeployment contentType res accept
req KubernetesRequest DeleteNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedDeployment 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 HasOptionalParam DeleteNamespacedDeployment DryRun where
applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept
-> DryRun
-> KubernetesRequest
DeleteNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedDeployment contentType res accept
req (DryRun Text
xs) =
KubernetesRequest DeleteNamespacedDeployment contentType res accept
req KubernetesRequest DeleteNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedDeployment 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 DeleteNamespacedDeployment GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedDeployment contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest DeleteNamespacedDeployment contentType res accept
req KubernetesRequest DeleteNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedDeployment contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteNamespacedDeployment OrphanDependents where
applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedDeployment contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest DeleteNamespacedDeployment contentType res accept
req KubernetesRequest DeleteNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedDeployment contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam DeleteNamespacedDeployment PropagationPolicy where
applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedDeployment contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest DeleteNamespacedDeployment contentType res accept
req KubernetesRequest DeleteNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedDeployment 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
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes DeleteNamespacedDeployment mtype
instance Produces DeleteNamespacedDeployment MimeJSON
instance Produces DeleteNamespacedDeployment MimeVndKubernetesProtobuf
instance Produces DeleteNamespacedDeployment MimeYaml
deleteNamespacedReplicaSet
:: (Consumes DeleteNamespacedReplicaSet contentType)
=> ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest DeleteNamespacedReplicaSet contentType V1Status accept
deleteNamespacedReplicaSet :: ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
DeleteNamespacedReplicaSet contentType V1Status accept
deleteNamespacedReplicaSet ContentType contentType
_ Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteNamespacedReplicaSet contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicasets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
DeleteNamespacedReplicaSet contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteNamespacedReplicaSet contentType V1Status 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 DeleteNamespacedReplicaSet
instance HasBodyParam DeleteNamespacedReplicaSet V1DeleteOptions
instance HasOptionalParam DeleteNamespacedReplicaSet Pretty where
applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
-> Pretty
-> KubernetesRequest
DeleteNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
req (Pretty Text
xs) =
KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
req KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedReplicaSet 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 HasOptionalParam DeleteNamespacedReplicaSet DryRun where
applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
-> DryRun
-> KubernetesRequest
DeleteNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
req (DryRun Text
xs) =
KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
req KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedReplicaSet 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 DeleteNamespacedReplicaSet GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
req KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedReplicaSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteNamespacedReplicaSet OrphanDependents where
applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
req KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedReplicaSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam DeleteNamespacedReplicaSet PropagationPolicy where
applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
req KubernetesRequest DeleteNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedReplicaSet 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
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes DeleteNamespacedReplicaSet mtype
instance Produces DeleteNamespacedReplicaSet MimeJSON
instance Produces DeleteNamespacedReplicaSet MimeVndKubernetesProtobuf
instance Produces DeleteNamespacedReplicaSet MimeYaml
deleteNamespacedStatefulSet
:: (Consumes DeleteNamespacedStatefulSet contentType)
=> ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest DeleteNamespacedStatefulSet contentType V1Status accept
deleteNamespacedStatefulSet :: ContentType contentType
-> Accept accept
-> Name
-> Namespace
-> KubernetesRequest
DeleteNamespacedStatefulSet contentType V1Status accept
deleteNamespacedStatefulSet ContentType contentType
_ Accept accept
_ (Name Text
name) (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteNamespacedStatefulSet contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/statefulsets/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
DeleteNamespacedStatefulSet contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteNamespacedStatefulSet contentType V1Status 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 DeleteNamespacedStatefulSet
instance HasBodyParam DeleteNamespacedStatefulSet V1DeleteOptions
instance HasOptionalParam DeleteNamespacedStatefulSet Pretty where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
-> Pretty
-> KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedStatefulSet 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 HasOptionalParam DeleteNamespacedStatefulSet DryRun where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
-> DryRun
-> KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedStatefulSet 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 DeleteNamespacedStatefulSet GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"gracePeriodSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam DeleteNamespacedStatefulSet OrphanDependents where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"orphanDependents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam DeleteNamespacedStatefulSet PropagationPolicy where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
req KubernetesRequest
DeleteNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedStatefulSet 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
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance MimeType mtype => Consumes DeleteNamespacedStatefulSet mtype
instance Produces DeleteNamespacedStatefulSet MimeJSON
instance Produces DeleteNamespacedStatefulSet MimeVndKubernetesProtobuf
instance Produces DeleteNamespacedStatefulSet 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/apps/v1beta2/"]
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
listControllerRevisionForAllNamespaces
:: Accept accept
-> KubernetesRequest ListControllerRevisionForAllNamespaces MimeNoContent V1beta2ControllerRevisionList accept
listControllerRevisionForAllNamespaces :: Accept accept
-> KubernetesRequest
ListControllerRevisionForAllNamespaces
MimeNoContent
V1beta2ControllerRevisionList
accept
listControllerRevisionForAllNamespaces Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
ListControllerRevisionForAllNamespaces
MimeNoContent
V1beta2ControllerRevisionList
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/apps/v1beta2/controllerrevisions"]
KubernetesRequest
ListControllerRevisionForAllNamespaces
MimeNoContent
V1beta2ControllerRevisionList
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListControllerRevisionForAllNamespaces
MimeNoContent
V1beta2ControllerRevisionList
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 ListControllerRevisionForAllNamespaces
instance HasOptionalParam ListControllerRevisionForAllNamespaces AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ListControllerRevisionForAllNamespaces Continue where
applyOptionalParam :: KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req (Continue Text
xs) =
KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListControllerRevisionForAllNamespaces 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListControllerRevisionForAllNamespaces FieldSelector where
applyOptionalParam :: KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListControllerRevisionForAllNamespaces 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListControllerRevisionForAllNamespaces LabelSelector where
applyOptionalParam :: KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListControllerRevisionForAllNamespaces 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListControllerRevisionForAllNamespaces Limit where
applyOptionalParam :: KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req (Limit Int
xs) =
KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListControllerRevisionForAllNamespaces Pretty where
applyOptionalParam :: KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListControllerRevisionForAllNamespaces 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 HasOptionalParam ListControllerRevisionForAllNamespaces ResourceVersion where
applyOptionalParam :: KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListControllerRevisionForAllNamespaces 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListControllerRevisionForAllNamespaces TimeoutSeconds where
applyOptionalParam :: KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListControllerRevisionForAllNamespaces Watch where
applyOptionalParam :: KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req (Watch Bool
xs) =
KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
req KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListControllerRevisionForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ListControllerRevisionForAllNamespaces MimeJSON
instance Produces ListControllerRevisionForAllNamespaces MimeJsonstreamwatch
instance Produces ListControllerRevisionForAllNamespaces MimeVndKubernetesProtobuf
instance Produces ListControllerRevisionForAllNamespaces MimeVndKubernetesProtobufstreamwatch
instance Produces ListControllerRevisionForAllNamespaces MimeYaml
listDaemonSetForAllNamespaces
:: Accept accept
-> KubernetesRequest ListDaemonSetForAllNamespaces MimeNoContent V1beta2DaemonSetList accept
listDaemonSetForAllNamespaces :: Accept accept
-> KubernetesRequest
ListDaemonSetForAllNamespaces
MimeNoContent
V1beta2DaemonSetList
accept
listDaemonSetForAllNamespaces Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
ListDaemonSetForAllNamespaces
MimeNoContent
V1beta2DaemonSetList
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/apps/v1beta2/daemonsets"]
KubernetesRequest
ListDaemonSetForAllNamespaces
MimeNoContent
V1beta2DaemonSetList
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListDaemonSetForAllNamespaces
MimeNoContent
V1beta2DaemonSetList
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 ListDaemonSetForAllNamespaces
instance HasOptionalParam ListDaemonSetForAllNamespaces AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ListDaemonSetForAllNamespaces Continue where
applyOptionalParam :: KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req (Continue Text
xs) =
KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDaemonSetForAllNamespaces 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListDaemonSetForAllNamespaces FieldSelector where
applyOptionalParam :: KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDaemonSetForAllNamespaces 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListDaemonSetForAllNamespaces LabelSelector where
applyOptionalParam :: KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDaemonSetForAllNamespaces 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListDaemonSetForAllNamespaces Limit where
applyOptionalParam :: KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req (Limit Int
xs) =
KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListDaemonSetForAllNamespaces Pretty where
applyOptionalParam :: KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDaemonSetForAllNamespaces 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 HasOptionalParam ListDaemonSetForAllNamespaces ResourceVersion where
applyOptionalParam :: KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDaemonSetForAllNamespaces 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListDaemonSetForAllNamespaces TimeoutSeconds where
applyOptionalParam :: KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListDaemonSetForAllNamespaces Watch where
applyOptionalParam :: KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req (Watch Bool
xs) =
KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
req KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDaemonSetForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ListDaemonSetForAllNamespaces MimeJSON
instance Produces ListDaemonSetForAllNamespaces MimeJsonstreamwatch
instance Produces ListDaemonSetForAllNamespaces MimeVndKubernetesProtobuf
instance Produces ListDaemonSetForAllNamespaces MimeVndKubernetesProtobufstreamwatch
instance Produces ListDaemonSetForAllNamespaces MimeYaml
listDeploymentForAllNamespaces
:: Accept accept
-> KubernetesRequest ListDeploymentForAllNamespaces MimeNoContent V1beta2DeploymentList accept
listDeploymentForAllNamespaces :: Accept accept
-> KubernetesRequest
ListDeploymentForAllNamespaces
MimeNoContent
V1beta2DeploymentList
accept
listDeploymentForAllNamespaces Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
ListDeploymentForAllNamespaces
MimeNoContent
V1beta2DeploymentList
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/apps/v1beta2/deployments"]
KubernetesRequest
ListDeploymentForAllNamespaces
MimeNoContent
V1beta2DeploymentList
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListDeploymentForAllNamespaces
MimeNoContent
V1beta2DeploymentList
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 ListDeploymentForAllNamespaces
instance HasOptionalParam ListDeploymentForAllNamespaces AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ListDeploymentForAllNamespaces Continue where
applyOptionalParam :: KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req (Continue Text
xs) =
KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDeploymentForAllNamespaces 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListDeploymentForAllNamespaces FieldSelector where
applyOptionalParam :: KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDeploymentForAllNamespaces 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListDeploymentForAllNamespaces LabelSelector where
applyOptionalParam :: KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDeploymentForAllNamespaces 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListDeploymentForAllNamespaces Limit where
applyOptionalParam :: KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req (Limit Int
xs) =
KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListDeploymentForAllNamespaces Pretty where
applyOptionalParam :: KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDeploymentForAllNamespaces 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 HasOptionalParam ListDeploymentForAllNamespaces ResourceVersion where
applyOptionalParam :: KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDeploymentForAllNamespaces 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListDeploymentForAllNamespaces TimeoutSeconds where
applyOptionalParam :: KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListDeploymentForAllNamespaces Watch where
applyOptionalParam :: KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req (Watch Bool
xs) =
KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
req KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListDeploymentForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ListDeploymentForAllNamespaces MimeJSON
instance Produces ListDeploymentForAllNamespaces MimeJsonstreamwatch
instance Produces ListDeploymentForAllNamespaces MimeVndKubernetesProtobuf
instance Produces ListDeploymentForAllNamespaces MimeVndKubernetesProtobufstreamwatch
instance Produces ListDeploymentForAllNamespaces MimeYaml
listNamespacedControllerRevision
:: Accept accept
-> Namespace
-> KubernetesRequest ListNamespacedControllerRevision MimeNoContent V1beta2ControllerRevisionList accept
listNamespacedControllerRevision :: Accept accept
-> Namespace
-> KubernetesRequest
ListNamespacedControllerRevision
MimeNoContent
V1beta2ControllerRevisionList
accept
listNamespacedControllerRevision Accept accept
_ (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
ListNamespacedControllerRevision
MimeNoContent
V1beta2ControllerRevisionList
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/controllerrevisions"]
KubernetesRequest
ListNamespacedControllerRevision
MimeNoContent
V1beta2ControllerRevisionList
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListNamespacedControllerRevision
MimeNoContent
V1beta2ControllerRevisionList
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 ListNamespacedControllerRevision
instance HasOptionalParam ListNamespacedControllerRevision Pretty where
applyOptionalParam :: KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> Pretty
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedControllerRevision 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 HasOptionalParam ListNamespacedControllerRevision AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ListNamespacedControllerRevision Continue where
applyOptionalParam :: KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> Continue
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req (Continue Text
xs) =
KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedControllerRevision 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedControllerRevision FieldSelector where
applyOptionalParam :: KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> FieldSelector
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedControllerRevision 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedControllerRevision LabelSelector where
applyOptionalParam :: KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> LabelSelector
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedControllerRevision 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedControllerRevision Limit where
applyOptionalParam :: KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> Limit
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req (Limit Int
xs) =
KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListNamespacedControllerRevision ResourceVersion where
applyOptionalParam :: KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> ResourceVersion
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedControllerRevision 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedControllerRevision TimeoutSeconds where
applyOptionalParam :: KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListNamespacedControllerRevision Watch where
applyOptionalParam :: KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> Watch
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
applyOptionalParam KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req (Watch Bool
xs) =
KubernetesRequest
ListNamespacedControllerRevision contentType res accept
req KubernetesRequest
ListNamespacedControllerRevision contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedControllerRevision contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ListNamespacedControllerRevision MimeJSON
instance Produces ListNamespacedControllerRevision MimeJsonstreamwatch
instance Produces ListNamespacedControllerRevision MimeVndKubernetesProtobuf
instance Produces ListNamespacedControllerRevision MimeVndKubernetesProtobufstreamwatch
instance Produces ListNamespacedControllerRevision MimeYaml
listNamespacedDaemonSet
:: Accept accept
-> Namespace
-> KubernetesRequest ListNamespacedDaemonSet MimeNoContent V1beta2DaemonSetList accept
listNamespacedDaemonSet :: Accept accept
-> Namespace
-> KubernetesRequest
ListNamespacedDaemonSet MimeNoContent V1beta2DaemonSetList accept
listNamespacedDaemonSet Accept accept
_ (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
ListNamespacedDaemonSet MimeNoContent V1beta2DaemonSetList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/daemonsets"]
KubernetesRequest
ListNamespacedDaemonSet MimeNoContent V1beta2DaemonSetList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListNamespacedDaemonSet MimeNoContent V1beta2DaemonSetList 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 ListNamespacedDaemonSet
instance HasOptionalParam ListNamespacedDaemonSet Pretty where
applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> Pretty
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDaemonSet contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ListNamespacedDaemonSet contentType res accept
req KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedDaemonSet 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 HasOptionalParam ListNamespacedDaemonSet AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDaemonSet contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest ListNamespacedDaemonSet contentType res accept
req KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ListNamespacedDaemonSet Continue where
applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> Continue
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDaemonSet contentType res accept
req (Continue Text
xs) =
KubernetesRequest ListNamespacedDaemonSet contentType res accept
req KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedDaemonSet 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedDaemonSet FieldSelector where
applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> FieldSelector
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDaemonSet contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest ListNamespacedDaemonSet contentType res accept
req KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedDaemonSet 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedDaemonSet LabelSelector where
applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> LabelSelector
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDaemonSet contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest ListNamespacedDaemonSet contentType res accept
req KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedDaemonSet 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedDaemonSet Limit where
applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> Limit
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDaemonSet contentType res accept
req (Limit Int
xs) =
KubernetesRequest ListNamespacedDaemonSet contentType res accept
req KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListNamespacedDaemonSet ResourceVersion where
applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> ResourceVersion
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDaemonSet contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest ListNamespacedDaemonSet contentType res accept
req KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedDaemonSet 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedDaemonSet TimeoutSeconds where
applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDaemonSet contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest ListNamespacedDaemonSet contentType res accept
req KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListNamespacedDaemonSet Watch where
applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> Watch
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDaemonSet contentType res accept
req (Watch Bool
xs) =
KubernetesRequest ListNamespacedDaemonSet contentType res accept
req KubernetesRequest ListNamespacedDaemonSet contentType res accept
-> [QueryItem]
-> KubernetesRequest ListNamespacedDaemonSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ListNamespacedDaemonSet MimeJSON
instance Produces ListNamespacedDaemonSet MimeJsonstreamwatch
instance Produces ListNamespacedDaemonSet MimeVndKubernetesProtobuf
instance Produces ListNamespacedDaemonSet MimeVndKubernetesProtobufstreamwatch
instance Produces ListNamespacedDaemonSet MimeYaml
listNamespacedDeployment
:: Accept accept
-> Namespace
-> KubernetesRequest ListNamespacedDeployment MimeNoContent V1beta2DeploymentList accept
listNamespacedDeployment :: Accept accept
-> Namespace
-> KubernetesRequest
ListNamespacedDeployment MimeNoContent V1beta2DeploymentList accept
listNamespacedDeployment Accept accept
_ (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
ListNamespacedDeployment MimeNoContent V1beta2DeploymentList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/deployments"]
KubernetesRequest
ListNamespacedDeployment MimeNoContent V1beta2DeploymentList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListNamespacedDeployment MimeNoContent V1beta2DeploymentList 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 ListNamespacedDeployment
instance HasOptionalParam ListNamespacedDeployment Pretty where
applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept
-> Pretty
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDeployment contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ListNamespacedDeployment contentType res accept
req KubernetesRequest ListNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedDeployment 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 HasOptionalParam ListNamespacedDeployment AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDeployment contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest ListNamespacedDeployment contentType res accept
req KubernetesRequest ListNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ListNamespacedDeployment Continue where
applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept
-> Continue
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDeployment contentType res accept
req (Continue Text
xs) =
KubernetesRequest ListNamespacedDeployment contentType res accept
req KubernetesRequest ListNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedDeployment 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedDeployment FieldSelector where
applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept
-> FieldSelector
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDeployment contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest ListNamespacedDeployment contentType res accept
req KubernetesRequest ListNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedDeployment 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedDeployment LabelSelector where
applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept
-> LabelSelector
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDeployment contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest ListNamespacedDeployment contentType res accept
req KubernetesRequest ListNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedDeployment 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedDeployment Limit where
applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept
-> Limit
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDeployment contentType res accept
req (Limit Int
xs) =
KubernetesRequest ListNamespacedDeployment contentType res accept
req KubernetesRequest ListNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListNamespacedDeployment ResourceVersion where
applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept
-> ResourceVersion
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDeployment contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest ListNamespacedDeployment contentType res accept
req KubernetesRequest ListNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedDeployment 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedDeployment TimeoutSeconds where
applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDeployment contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest ListNamespacedDeployment contentType res accept
req KubernetesRequest ListNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListNamespacedDeployment Watch where
applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept
-> Watch
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedDeployment contentType res accept
req (Watch Bool
xs) =
KubernetesRequest ListNamespacedDeployment contentType res accept
req KubernetesRequest ListNamespacedDeployment contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedDeployment contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ListNamespacedDeployment MimeJSON
instance Produces ListNamespacedDeployment MimeJsonstreamwatch
instance Produces ListNamespacedDeployment MimeVndKubernetesProtobuf
instance Produces ListNamespacedDeployment MimeVndKubernetesProtobufstreamwatch
instance Produces ListNamespacedDeployment MimeYaml
listNamespacedReplicaSet
:: Accept accept
-> Namespace
-> KubernetesRequest ListNamespacedReplicaSet MimeNoContent V1beta2ReplicaSetList accept
listNamespacedReplicaSet :: Accept accept
-> Namespace
-> KubernetesRequest
ListNamespacedReplicaSet MimeNoContent V1beta2ReplicaSetList accept
listNamespacedReplicaSet Accept accept
_ (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
ListNamespacedReplicaSet MimeNoContent V1beta2ReplicaSetList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/replicasets"]
KubernetesRequest
ListNamespacedReplicaSet MimeNoContent V1beta2ReplicaSetList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListNamespacedReplicaSet MimeNoContent V1beta2ReplicaSetList 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 ListNamespacedReplicaSet
instance HasOptionalParam ListNamespacedReplicaSet Pretty where
applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> Pretty
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedReplicaSet contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ListNamespacedReplicaSet contentType res accept
req KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedReplicaSet 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 HasOptionalParam ListNamespacedReplicaSet AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedReplicaSet contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest ListNamespacedReplicaSet contentType res accept
req KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ListNamespacedReplicaSet Continue where
applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> Continue
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedReplicaSet contentType res accept
req (Continue Text
xs) =
KubernetesRequest ListNamespacedReplicaSet contentType res accept
req KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedReplicaSet 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedReplicaSet FieldSelector where
applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> FieldSelector
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedReplicaSet contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest ListNamespacedReplicaSet contentType res accept
req KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedReplicaSet 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedReplicaSet LabelSelector where
applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> LabelSelector
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedReplicaSet contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest ListNamespacedReplicaSet contentType res accept
req KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedReplicaSet 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedReplicaSet Limit where
applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> Limit
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedReplicaSet contentType res accept
req (Limit Int
xs) =
KubernetesRequest ListNamespacedReplicaSet contentType res accept
req KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListNamespacedReplicaSet ResourceVersion where
applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> ResourceVersion
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedReplicaSet contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest ListNamespacedReplicaSet contentType res accept
req KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedReplicaSet 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedReplicaSet TimeoutSeconds where
applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedReplicaSet contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest ListNamespacedReplicaSet contentType res accept
req KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListNamespacedReplicaSet Watch where
applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> Watch
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedReplicaSet contentType res accept
req (Watch Bool
xs) =
KubernetesRequest ListNamespacedReplicaSet contentType res accept
req KubernetesRequest ListNamespacedReplicaSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedReplicaSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ListNamespacedReplicaSet MimeJSON
instance Produces ListNamespacedReplicaSet MimeJsonstreamwatch
instance Produces ListNamespacedReplicaSet MimeVndKubernetesProtobuf
instance Produces ListNamespacedReplicaSet MimeVndKubernetesProtobufstreamwatch
instance Produces ListNamespacedReplicaSet MimeYaml
listNamespacedStatefulSet
:: Accept accept
-> Namespace
-> KubernetesRequest ListNamespacedStatefulSet MimeNoContent V1beta2StatefulSetList accept
listNamespacedStatefulSet :: Accept accept
-> Namespace
-> KubernetesRequest
ListNamespacedStatefulSet
MimeNoContent
V1beta2StatefulSetList
accept
listNamespacedStatefulSet Accept accept
_ (Namespace Text
namespace) =
Method
-> [ByteString]
-> KubernetesRequest
ListNamespacedStatefulSet
MimeNoContent
V1beta2StatefulSetList
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/apps/v1beta2/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/statefulsets"]
KubernetesRequest
ListNamespacedStatefulSet
MimeNoContent
V1beta2StatefulSetList
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListNamespacedStatefulSet
MimeNoContent
V1beta2StatefulSetList
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 ListNamespacedStatefulSet
instance HasOptionalParam ListNamespacedStatefulSet Pretty where
applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> Pretty
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedStatefulSet contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ListNamespacedStatefulSet contentType res accept
req KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedStatefulSet 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 HasOptionalParam ListNamespacedStatefulSet AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedStatefulSet contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest ListNamespacedStatefulSet contentType res accept
req KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ListNamespacedStatefulSet Continue where
applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> Continue
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedStatefulSet contentType res accept
req (Continue Text
xs) =
KubernetesRequest ListNamespacedStatefulSet contentType res accept
req KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedStatefulSet 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedStatefulSet FieldSelector where
applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> FieldSelector
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedStatefulSet contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest ListNamespacedStatefulSet contentType res accept
req KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedStatefulSet 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedStatefulSet LabelSelector where
applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> LabelSelector
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedStatefulSet contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest ListNamespacedStatefulSet contentType res accept
req KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedStatefulSet 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedStatefulSet Limit where
applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> Limit
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedStatefulSet contentType res accept
req (Limit Int
xs) =
KubernetesRequest ListNamespacedStatefulSet contentType res accept
req KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListNamespacedStatefulSet ResourceVersion where
applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> ResourceVersion
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedStatefulSet contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest ListNamespacedStatefulSet contentType res accept
req KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedStatefulSet 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListNamespacedStatefulSet TimeoutSeconds where
applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedStatefulSet contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest ListNamespacedStatefulSet contentType res accept
req KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListNamespacedStatefulSet Watch where
applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> Watch
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedStatefulSet contentType res accept
req (Watch Bool
xs) =
KubernetesRequest ListNamespacedStatefulSet contentType res accept
req KubernetesRequest ListNamespacedStatefulSet contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedStatefulSet contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ListNamespacedStatefulSet MimeJSON
instance Produces ListNamespacedStatefulSet MimeJsonstreamwatch
instance Produces ListNamespacedStatefulSet MimeVndKubernetesProtobuf
instance Produces ListNamespacedStatefulSet MimeVndKubernetesProtobufstreamwatch
instance Produces ListNamespacedStatefulSet MimeYaml
listReplicaSetForAllNamespaces
:: Accept accept
-> KubernetesRequest ListReplicaSetForAllNamespaces MimeNoContent V1beta2ReplicaSetList accept
listReplicaSetForAllNamespaces :: Accept accept
-> KubernetesRequest
ListReplicaSetForAllNamespaces
MimeNoContent
V1beta2ReplicaSetList
accept
listReplicaSetForAllNamespaces Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
ListReplicaSetForAllNamespaces
MimeNoContent
V1beta2ReplicaSetList
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/apps/v1beta2/replicasets"]
KubernetesRequest
ListReplicaSetForAllNamespaces
MimeNoContent
V1beta2ReplicaSetList
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListReplicaSetForAllNamespaces
MimeNoContent
V1beta2ReplicaSetList
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 ListReplicaSetForAllNamespaces
instance HasOptionalParam ListReplicaSetForAllNamespaces AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ListReplicaSetForAllNamespaces Continue where
applyOptionalParam :: KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req (Continue Text
xs) =
KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListReplicaSetForAllNamespaces 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListReplicaSetForAllNamespaces FieldSelector where
applyOptionalParam :: KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListReplicaSetForAllNamespaces 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListReplicaSetForAllNamespaces LabelSelector where
applyOptionalParam :: KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListReplicaSetForAllNamespaces 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListReplicaSetForAllNamespaces Limit where
applyOptionalParam :: KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req (Limit Int
xs) =
KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"limit", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListReplicaSetForAllNamespaces Pretty where
applyOptionalParam :: KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> Pretty
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListReplicaSetForAllNamespaces 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 HasOptionalParam ListReplicaSetForAllNamespaces ResourceVersion where
applyOptionalParam :: KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> ResourceVersion
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListReplicaSetForAllNamespaces 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
"resourceVersion", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListReplicaSetForAllNamespaces TimeoutSeconds where
applyOptionalParam :: KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)
instance HasOptionalParam ListReplicaSetForAllNamespaces Watch where
applyOptionalParam :: KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> Watch
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req (Watch Bool
xs) =
KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
req KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListReplicaSetForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"watch", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Produces ListReplicaSetForAllNamespaces MimeJSON
instance Produces ListReplicaSetForAllNamespaces MimeJsonstreamwatch
instance Produces ListReplicaSetForAllNamespaces MimeVndKubernetesProtobuf
instance Produces ListReplicaSetForAllNamespaces MimeVndKubernetesProtobufstreamwatch
instance Produces ListReplicaSetForAllNamespaces MimeYaml
listStatefulSetForAllNamespaces
:: Accept accept
-> KubernetesRequest ListStatefulSetForAllNamespaces MimeNoContent V1beta2StatefulSetList accept
listStatefulSetForAllNamespaces :: Accept accept
-> KubernetesRequest
ListStatefulSetForAllNamespaces
MimeNoContent
V1beta2StatefulSetList
accept
listStatefulSetForAllNamespaces Accept accept
_ =
Method
-> [ByteString]
-> KubernetesRequest
ListStatefulSetForAllNamespaces
MimeNoContent
V1beta2StatefulSetList
accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/apps/v1beta2/statefulsets"]
KubernetesRequest
ListStatefulSetForAllNamespaces
MimeNoContent
V1beta2StatefulSetList
accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListStatefulSetForAllNamespaces
MimeNoContent
V1beta2StatefulSetList
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 ListStatefulSetForAllNamespaces
instance HasOptionalParam ListStatefulSetForAllNamespaces AllowWatchBookmarks where
applyOptionalParam :: KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
req (AllowWatchBookmarks Bool
xs) =
KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
req KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance HasOptionalParam ListStatefulSetForAllNamespaces Continue where
applyOptionalParam :: KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
-> Continue
-> KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
req (Continue Text
xs) =
KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
req KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListStatefulSetForAllNamespaces 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
"continue", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListStatefulSetForAllNamespaces FieldSelector where
applyOptionalParam :: KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
-> FieldSelector
-> KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
req KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListStatefulSetForAllNamespaces 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
"fieldSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListStatefulSetForAllNamespaces LabelSelector where
applyOptionalParam :: KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
-> LabelSelector
-> KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
applyOptionalParam KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
req KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListStatefulSetForAllNamespaces 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
"labelSelector", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam ListStatefulSetForAllNamespaces Limit where
applyOptionalParam :: KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept
-> Limit
-> KubernetesRequest
ListStatefulSetForAllNamespaces contentType res accept