{-# 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.CustomObjects 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
createClusterCustomObject
:: (Consumes CreateClusterCustomObject contentType, MimeRender contentType Body)
=> ContentType contentType
-> Body
-> Group
-> Version
-> Plural
-> KubernetesRequest CreateClusterCustomObject contentType A.Value MimeJSON
createClusterCustomObject :: ContentType contentType
-> Body
-> Group
-> Version
-> Plural
-> KubernetesRequest
CreateClusterCustomObject contentType Value MimeJSON
createClusterCustomObject ContentType contentType
_ Body
body (Group Text
group) (Version Text
version) (Plural Text
plural) =
Method
-> [ByteString]
-> KubernetesRequest
CreateClusterCustomObject contentType Value MimeJSON
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural]
KubernetesRequest
CreateClusterCustomObject contentType Value MimeJSON
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateClusterCustomObject contentType Value MimeJSON
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
CreateClusterCustomObject contentType Value MimeJSON
-> Body
-> KubernetesRequest
CreateClusterCustomObject contentType Value MimeJSON
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` Body
body
data CreateClusterCustomObject
instance HasBodyParam CreateClusterCustomObject Body
instance HasOptionalParam CreateClusterCustomObject Pretty where
applyOptionalParam :: KubernetesRequest CreateClusterCustomObject contentType res accept
-> Pretty
-> KubernetesRequest
CreateClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest CreateClusterCustomObject contentType res accept
req (Pretty Text
xs) =
KubernetesRequest CreateClusterCustomObject contentType res accept
req KubernetesRequest CreateClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateClusterCustomObject 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 CreateClusterCustomObject DryRun where
applyOptionalParam :: KubernetesRequest CreateClusterCustomObject contentType res accept
-> DryRun
-> KubernetesRequest
CreateClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest CreateClusterCustomObject contentType res accept
req (DryRun Text
xs) =
KubernetesRequest CreateClusterCustomObject contentType res accept
req KubernetesRequest CreateClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateClusterCustomObject 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 CreateClusterCustomObject FieldManager where
applyOptionalParam :: KubernetesRequest CreateClusterCustomObject contentType res accept
-> FieldManager
-> KubernetesRequest
CreateClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest CreateClusterCustomObject contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest CreateClusterCustomObject contentType res accept
req KubernetesRequest CreateClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateClusterCustomObject 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 CreateClusterCustomObject mtype
instance Produces CreateClusterCustomObject MimeJSON
createNamespacedCustomObject
:: (Consumes CreateNamespacedCustomObject contentType, MimeRender contentType Body)
=> ContentType contentType
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> KubernetesRequest CreateNamespacedCustomObject contentType A.Value MimeJSON
createNamespacedCustomObject :: ContentType contentType
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> KubernetesRequest
CreateNamespacedCustomObject contentType Value MimeJSON
createNamespacedCustomObject ContentType contentType
_ Body
body (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) =
Method
-> [ByteString]
-> KubernetesRequest
CreateNamespacedCustomObject contentType Value MimeJSON
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural]
KubernetesRequest
CreateNamespacedCustomObject contentType Value MimeJSON
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
CreateNamespacedCustomObject contentType Value MimeJSON
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
CreateNamespacedCustomObject contentType Value MimeJSON
-> Body
-> KubernetesRequest
CreateNamespacedCustomObject contentType Value MimeJSON
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` Body
body
data CreateNamespacedCustomObject
instance HasBodyParam CreateNamespacedCustomObject Body
instance HasOptionalParam CreateNamespacedCustomObject Pretty where
applyOptionalParam :: KubernetesRequest
CreateNamespacedCustomObject contentType res accept
-> Pretty
-> KubernetesRequest
CreateNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
CreateNamespacedCustomObject contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
CreateNamespacedCustomObject contentType res accept
req KubernetesRequest
CreateNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedCustomObject 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 CreateNamespacedCustomObject DryRun where
applyOptionalParam :: KubernetesRequest
CreateNamespacedCustomObject contentType res accept
-> DryRun
-> KubernetesRequest
CreateNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
CreateNamespacedCustomObject contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
CreateNamespacedCustomObject contentType res accept
req KubernetesRequest
CreateNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedCustomObject 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 CreateNamespacedCustomObject FieldManager where
applyOptionalParam :: KubernetesRequest
CreateNamespacedCustomObject contentType res accept
-> FieldManager
-> KubernetesRequest
CreateNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
CreateNamespacedCustomObject contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
CreateNamespacedCustomObject contentType res accept
req KubernetesRequest
CreateNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
CreateNamespacedCustomObject 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 CreateNamespacedCustomObject mtype
instance Produces CreateNamespacedCustomObject MimeJSON
deleteClusterCustomObject
:: (Consumes DeleteClusterCustomObject contentType)
=> ContentType contentType
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest DeleteClusterCustomObject contentType A.Value MimeJSON
deleteClusterCustomObject :: ContentType contentType
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest
DeleteClusterCustomObject contentType Value MimeJSON
deleteClusterCustomObject ContentType contentType
_ (Group Text
group) (Version Text
version) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteClusterCustomObject contentType Value MimeJSON
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
DeleteClusterCustomObject contentType Value MimeJSON
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteClusterCustomObject contentType Value MimeJSON
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 DeleteClusterCustomObject
instance HasBodyParam DeleteClusterCustomObject V1DeleteOptions
instance HasOptionalParam DeleteClusterCustomObject GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest DeleteClusterCustomObject contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest DeleteClusterCustomObject contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest DeleteClusterCustomObject contentType res accept
req KubernetesRequest DeleteClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteClusterCustomObject 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 DeleteClusterCustomObject OrphanDependents where
applyOptionalParam :: KubernetesRequest DeleteClusterCustomObject contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest DeleteClusterCustomObject contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest DeleteClusterCustomObject contentType res accept
req KubernetesRequest DeleteClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteClusterCustomObject 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 DeleteClusterCustomObject PropagationPolicy where
applyOptionalParam :: KubernetesRequest DeleteClusterCustomObject contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest DeleteClusterCustomObject contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest DeleteClusterCustomObject contentType res accept
req KubernetesRequest DeleteClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteClusterCustomObject 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 DeleteClusterCustomObject DryRun where
applyOptionalParam :: KubernetesRequest DeleteClusterCustomObject contentType res accept
-> DryRun
-> KubernetesRequest
DeleteClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest DeleteClusterCustomObject contentType res accept
req (DryRun Text
xs) =
KubernetesRequest DeleteClusterCustomObject contentType res accept
req KubernetesRequest DeleteClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteClusterCustomObject 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 MimeType mtype => Consumes DeleteClusterCustomObject mtype
instance Produces DeleteClusterCustomObject MimeJSON
deleteCollectionClusterCustomObject
:: (Consumes DeleteCollectionClusterCustomObject contentType)
=> ContentType contentType
-> Group
-> Version
-> Plural
-> KubernetesRequest DeleteCollectionClusterCustomObject contentType A.Value MimeJSON
deleteCollectionClusterCustomObject :: ContentType contentType
-> Group
-> Version
-> Plural
-> KubernetesRequest
DeleteCollectionClusterCustomObject contentType Value MimeJSON
deleteCollectionClusterCustomObject ContentType contentType
_ (Group Text
group) (Version Text
version) (Plural Text
plural) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteCollectionClusterCustomObject contentType Value MimeJSON
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural]
KubernetesRequest
DeleteCollectionClusterCustomObject contentType Value MimeJSON
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteCollectionClusterCustomObject contentType Value MimeJSON
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 DeleteCollectionClusterCustomObject
instance HasBodyParam DeleteCollectionClusterCustomObject V1DeleteOptions
instance HasOptionalParam DeleteCollectionClusterCustomObject Pretty where
applyOptionalParam :: KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
-> Pretty
-> KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
req KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionClusterCustomObject 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 DeleteCollectionClusterCustomObject GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
req KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionClusterCustomObject 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 DeleteCollectionClusterCustomObject OrphanDependents where
applyOptionalParam :: KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
req KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionClusterCustomObject 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 DeleteCollectionClusterCustomObject PropagationPolicy where
applyOptionalParam :: KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
req KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionClusterCustomObject 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 DeleteCollectionClusterCustomObject DryRun where
applyOptionalParam :: KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
-> DryRun
-> KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
req KubernetesRequest
DeleteCollectionClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionClusterCustomObject 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 MimeType mtype => Consumes DeleteCollectionClusterCustomObject mtype
instance Produces DeleteCollectionClusterCustomObject MimeJSON
deleteCollectionNamespacedCustomObject
:: (Consumes DeleteCollectionNamespacedCustomObject contentType)
=> ContentType contentType
-> Group
-> Version
-> Namespace
-> Plural
-> KubernetesRequest DeleteCollectionNamespacedCustomObject contentType A.Value MimeJSON
deleteCollectionNamespacedCustomObject :: ContentType contentType
-> Group
-> Version
-> Namespace
-> Plural
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType Value MimeJSON
deleteCollectionNamespacedCustomObject ContentType contentType
_ (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType Value MimeJSON
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural]
KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType Value MimeJSON
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType Value MimeJSON
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 DeleteCollectionNamespacedCustomObject
instance HasBodyParam DeleteCollectionNamespacedCustomObject V1DeleteOptions
instance HasOptionalParam DeleteCollectionNamespacedCustomObject Pretty where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
-> Pretty
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
req (Pretty Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject 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 DeleteCollectionNamespacedCustomObject GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject 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 DeleteCollectionNamespacedCustomObject OrphanDependents where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject 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 DeleteCollectionNamespacedCustomObject PropagationPolicy where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject 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 DeleteCollectionNamespacedCustomObject DryRun where
applyOptionalParam :: KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
-> DryRun
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
req KubernetesRequest
DeleteCollectionNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteCollectionNamespacedCustomObject 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 MimeType mtype => Consumes DeleteCollectionNamespacedCustomObject mtype
instance Produces DeleteCollectionNamespacedCustomObject MimeJSON
deleteNamespacedCustomObject
:: (Consumes DeleteNamespacedCustomObject contentType)
=> ContentType contentType
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest DeleteNamespacedCustomObject contentType A.Value MimeJSON
deleteNamespacedCustomObject :: ContentType contentType
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest
DeleteNamespacedCustomObject contentType Value MimeJSON
deleteNamespacedCustomObject ContentType contentType
_ (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
DeleteNamespacedCustomObject contentType Value MimeJSON
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
DeleteNamespacedCustomObject contentType Value MimeJSON
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
DeleteNamespacedCustomObject contentType Value MimeJSON
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 DeleteNamespacedCustomObject
instance HasBodyParam DeleteNamespacedCustomObject V1DeleteOptions
instance HasOptionalParam DeleteNamespacedCustomObject GracePeriodSeconds where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
req (GracePeriodSeconds Int
xs) =
KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
req KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedCustomObject 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 DeleteNamespacedCustomObject OrphanDependents where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
-> OrphanDependents
-> KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
req (OrphanDependents Bool
xs) =
KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
req KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedCustomObject 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 DeleteNamespacedCustomObject PropagationPolicy where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
-> PropagationPolicy
-> KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
req (PropagationPolicy Text
xs) =
KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
req KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedCustomObject 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 DeleteNamespacedCustomObject DryRun where
applyOptionalParam :: KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
-> DryRun
-> KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
req KubernetesRequest
DeleteNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
DeleteNamespacedCustomObject 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 MimeType mtype => Consumes DeleteNamespacedCustomObject mtype
instance Produces DeleteNamespacedCustomObject MimeJSON
getClusterCustomObject
:: Group
-> Version
-> Plural
-> Name
-> KubernetesRequest GetClusterCustomObject MimeNoContent A.Value MimeJSON
getClusterCustomObject :: Group
-> Version
-> Plural
-> Name
-> KubernetesRequest
GetClusterCustomObject MimeNoContent Value MimeJSON
getClusterCustomObject (Group Text
group) (Version Text
version) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
GetClusterCustomObject MimeNoContent Value MimeJSON
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
GetClusterCustomObject MimeNoContent Value MimeJSON
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
GetClusterCustomObject MimeNoContent Value MimeJSON
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 GetClusterCustomObject
instance Produces GetClusterCustomObject MimeJSON
getClusterCustomObjectScale
:: Accept accept
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest GetClusterCustomObjectScale MimeNoContent A.Value accept
getClusterCustomObjectScale :: Accept accept
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest
GetClusterCustomObjectScale MimeNoContent Value accept
getClusterCustomObjectScale Accept accept
_ (Group Text
group) (Version Text
version) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
GetClusterCustomObjectScale MimeNoContent Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/scale"]
KubernetesRequest
GetClusterCustomObjectScale MimeNoContent Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
GetClusterCustomObjectScale MimeNoContent Value 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 GetClusterCustomObjectScale
instance Produces GetClusterCustomObjectScale MimeJSON
instance Produces GetClusterCustomObjectScale MimeVndKubernetesProtobuf
instance Produces GetClusterCustomObjectScale MimeYaml
getClusterCustomObjectStatus
:: Accept accept
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest GetClusterCustomObjectStatus MimeNoContent A.Value accept
getClusterCustomObjectStatus :: Accept accept
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest
GetClusterCustomObjectStatus MimeNoContent Value accept
getClusterCustomObjectStatus Accept accept
_ (Group Text
group) (Version Text
version) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
GetClusterCustomObjectStatus MimeNoContent Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
KubernetesRequest
GetClusterCustomObjectStatus MimeNoContent Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
GetClusterCustomObjectStatus MimeNoContent Value 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 GetClusterCustomObjectStatus
instance Produces GetClusterCustomObjectStatus MimeJSON
instance Produces GetClusterCustomObjectStatus MimeVndKubernetesProtobuf
instance Produces GetClusterCustomObjectStatus MimeYaml
getNamespacedCustomObject
:: Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest GetNamespacedCustomObject MimeNoContent A.Value MimeJSON
getNamespacedCustomObject :: Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest
GetNamespacedCustomObject MimeNoContent Value MimeJSON
getNamespacedCustomObject (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
GetNamespacedCustomObject MimeNoContent Value MimeJSON
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
GetNamespacedCustomObject MimeNoContent Value MimeJSON
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
GetNamespacedCustomObject MimeNoContent Value MimeJSON
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 GetNamespacedCustomObject
instance Produces GetNamespacedCustomObject MimeJSON
getNamespacedCustomObjectScale
:: Accept accept
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest GetNamespacedCustomObjectScale MimeNoContent A.Value accept
getNamespacedCustomObjectScale :: Accept accept
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest
GetNamespacedCustomObjectScale MimeNoContent Value accept
getNamespacedCustomObjectScale Accept accept
_ (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
GetNamespacedCustomObjectScale MimeNoContent Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/scale"]
KubernetesRequest
GetNamespacedCustomObjectScale MimeNoContent Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
GetNamespacedCustomObjectScale MimeNoContent Value 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 GetNamespacedCustomObjectScale
instance Produces GetNamespacedCustomObjectScale MimeJSON
instance Produces GetNamespacedCustomObjectScale MimeVndKubernetesProtobuf
instance Produces GetNamespacedCustomObjectScale MimeYaml
getNamespacedCustomObjectStatus
:: Accept accept
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest GetNamespacedCustomObjectStatus MimeNoContent A.Value accept
getNamespacedCustomObjectStatus :: Accept accept
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest
GetNamespacedCustomObjectStatus MimeNoContent Value accept
getNamespacedCustomObjectStatus Accept accept
_ (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
GetNamespacedCustomObjectStatus MimeNoContent Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
KubernetesRequest
GetNamespacedCustomObjectStatus MimeNoContent Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
GetNamespacedCustomObjectStatus MimeNoContent Value 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 GetNamespacedCustomObjectStatus
instance Produces GetNamespacedCustomObjectStatus MimeJSON
instance Produces GetNamespacedCustomObjectStatus MimeVndKubernetesProtobuf
instance Produces GetNamespacedCustomObjectStatus MimeYaml
listClusterCustomObject
:: Accept accept
-> Group
-> Version
-> Plural
-> KubernetesRequest ListClusterCustomObject MimeNoContent A.Value accept
listClusterCustomObject :: Accept accept
-> Group
-> Version
-> Plural
-> KubernetesRequest
ListClusterCustomObject MimeNoContent Value accept
listClusterCustomObject Accept accept
_ (Group Text
group) (Version Text
version) (Plural Text
plural) =
Method
-> [ByteString]
-> KubernetesRequest
ListClusterCustomObject MimeNoContent Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural]
KubernetesRequest
ListClusterCustomObject MimeNoContent Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListClusterCustomObject MimeNoContent Value 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 ListClusterCustomObject
instance HasOptionalParam ListClusterCustomObject Pretty where
applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept
-> Pretty
-> KubernetesRequest ListClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListClusterCustomObject contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ListClusterCustomObject contentType res accept
req KubernetesRequest ListClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest ListClusterCustomObject 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 ListClusterCustomObject Continue where
applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept
-> Continue
-> KubernetesRequest ListClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListClusterCustomObject contentType res accept
req (Continue Text
xs) =
KubernetesRequest ListClusterCustomObject contentType res accept
req KubernetesRequest ListClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest ListClusterCustomObject 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 ListClusterCustomObject FieldSelector where
applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept
-> FieldSelector
-> KubernetesRequest ListClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListClusterCustomObject contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest ListClusterCustomObject contentType res accept
req KubernetesRequest ListClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest ListClusterCustomObject 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 ListClusterCustomObject LabelSelector where
applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept
-> LabelSelector
-> KubernetesRequest ListClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListClusterCustomObject contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest ListClusterCustomObject contentType res accept
req KubernetesRequest ListClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest ListClusterCustomObject 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 ListClusterCustomObject Limit where
applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept
-> Limit
-> KubernetesRequest ListClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListClusterCustomObject contentType res accept
req (Limit Int
xs) =
KubernetesRequest ListClusterCustomObject contentType res accept
req KubernetesRequest ListClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest ListClusterCustomObject 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 ListClusterCustomObject ResourceVersion where
applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept
-> ResourceVersion
-> KubernetesRequest ListClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListClusterCustomObject contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest ListClusterCustomObject contentType res accept
req KubernetesRequest ListClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest ListClusterCustomObject 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 ListClusterCustomObject TimeoutSeconds where
applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListClusterCustomObject contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest ListClusterCustomObject contentType res accept
req KubernetesRequest ListClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest ListClusterCustomObject 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 ListClusterCustomObject Watch where
applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept
-> Watch
-> KubernetesRequest ListClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListClusterCustomObject contentType res accept
req (Watch Bool
xs) =
KubernetesRequest ListClusterCustomObject contentType res accept
req KubernetesRequest ListClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest ListClusterCustomObject 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 ListClusterCustomObject MimeJSON
instance Produces ListClusterCustomObject MimeJsonstreamwatch
listNamespacedCustomObject
:: Accept accept
-> Group
-> Version
-> Namespace
-> Plural
-> KubernetesRequest ListNamespacedCustomObject MimeNoContent A.Value accept
listNamespacedCustomObject :: Accept accept
-> Group
-> Version
-> Namespace
-> Plural
-> KubernetesRequest
ListNamespacedCustomObject MimeNoContent Value accept
listNamespacedCustomObject Accept accept
_ (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) =
Method
-> [ByteString]
-> KubernetesRequest
ListNamespacedCustomObject MimeNoContent Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural]
KubernetesRequest
ListNamespacedCustomObject MimeNoContent Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ListNamespacedCustomObject MimeNoContent Value 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 ListNamespacedCustomObject
instance HasOptionalParam ListNamespacedCustomObject Pretty where
applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept
-> Pretty
-> KubernetesRequest
ListNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedCustomObject contentType res accept
req (Pretty Text
xs) =
KubernetesRequest ListNamespacedCustomObject contentType res accept
req KubernetesRequest ListNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedCustomObject 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 ListNamespacedCustomObject Continue where
applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept
-> Continue
-> KubernetesRequest
ListNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedCustomObject contentType res accept
req (Continue Text
xs) =
KubernetesRequest ListNamespacedCustomObject contentType res accept
req KubernetesRequest ListNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedCustomObject 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 ListNamespacedCustomObject FieldSelector where
applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept
-> FieldSelector
-> KubernetesRequest
ListNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedCustomObject contentType res accept
req (FieldSelector Text
xs) =
KubernetesRequest ListNamespacedCustomObject contentType res accept
req KubernetesRequest ListNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedCustomObject 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 ListNamespacedCustomObject LabelSelector where
applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept
-> LabelSelector
-> KubernetesRequest
ListNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedCustomObject contentType res accept
req (LabelSelector Text
xs) =
KubernetesRequest ListNamespacedCustomObject contentType res accept
req KubernetesRequest ListNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedCustomObject 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 ListNamespacedCustomObject Limit where
applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept
-> Limit
-> KubernetesRequest
ListNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedCustomObject contentType res accept
req (Limit Int
xs) =
KubernetesRequest ListNamespacedCustomObject contentType res accept
req KubernetesRequest ListNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedCustomObject 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 ListNamespacedCustomObject ResourceVersion where
applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept
-> ResourceVersion
-> KubernetesRequest
ListNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedCustomObject contentType res accept
req (ResourceVersion Text
xs) =
KubernetesRequest ListNamespacedCustomObject contentType res accept
req KubernetesRequest ListNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedCustomObject 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 ListNamespacedCustomObject TimeoutSeconds where
applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
ListNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedCustomObject contentType res accept
req (TimeoutSeconds Int
xs) =
KubernetesRequest ListNamespacedCustomObject contentType res accept
req KubernetesRequest ListNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedCustomObject 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 ListNamespacedCustomObject Watch where
applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept
-> Watch
-> KubernetesRequest
ListNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest ListNamespacedCustomObject contentType res accept
req (Watch Bool
xs) =
KubernetesRequest ListNamespacedCustomObject contentType res accept
req KubernetesRequest ListNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
ListNamespacedCustomObject 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 ListNamespacedCustomObject MimeJSON
instance Produces ListNamespacedCustomObject MimeJsonstreamwatch
patchClusterCustomObject
:: (Consumes PatchClusterCustomObject contentType, MimeRender contentType Body)
=> ContentType contentType
-> Body
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest PatchClusterCustomObject contentType A.Value MimeJSON
patchClusterCustomObject :: ContentType contentType
-> Body
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest
PatchClusterCustomObject contentType Value MimeJSON
patchClusterCustomObject ContentType contentType
_ Body
body (Group Text
group) (Version Text
version) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
PatchClusterCustomObject contentType Value MimeJSON
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
PatchClusterCustomObject contentType Value MimeJSON
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
PatchClusterCustomObject contentType Value MimeJSON
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
PatchClusterCustomObject contentType Value MimeJSON
-> Body
-> KubernetesRequest
PatchClusterCustomObject contentType Value MimeJSON
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` Body
body
data PatchClusterCustomObject
instance HasBodyParam PatchClusterCustomObject Body
instance HasOptionalParam PatchClusterCustomObject DryRun where
applyOptionalParam :: KubernetesRequest PatchClusterCustomObject contentType res accept
-> DryRun
-> KubernetesRequest
PatchClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest PatchClusterCustomObject contentType res accept
req (DryRun Text
xs) =
KubernetesRequest PatchClusterCustomObject contentType res accept
req KubernetesRequest PatchClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchClusterCustomObject 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 PatchClusterCustomObject FieldManager where
applyOptionalParam :: KubernetesRequest PatchClusterCustomObject contentType res accept
-> FieldManager
-> KubernetesRequest
PatchClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest PatchClusterCustomObject contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest PatchClusterCustomObject contentType res accept
req KubernetesRequest PatchClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchClusterCustomObject contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam PatchClusterCustomObject Force where
applyOptionalParam :: KubernetesRequest PatchClusterCustomObject contentType res accept
-> Force
-> KubernetesRequest
PatchClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest PatchClusterCustomObject contentType res accept
req (Force Bool
xs) =
KubernetesRequest PatchClusterCustomObject contentType res accept
req KubernetesRequest PatchClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchClusterCustomObject 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
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Consumes PatchClusterCustomObject MimeJsonPatchjson
instance Consumes PatchClusterCustomObject MimeMergePatchjson
instance Produces PatchClusterCustomObject MimeJSON
patchClusterCustomObjectScale
:: (Consumes PatchClusterCustomObjectScale contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest PatchClusterCustomObjectScale contentType A.Value accept
patchClusterCustomObjectScale :: ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest
PatchClusterCustomObjectScale contentType Value accept
patchClusterCustomObjectScale ContentType contentType
_ Accept accept
_ Body
body (Group Text
group) (Version Text
version) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
PatchClusterCustomObjectScale contentType Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/scale"]
KubernetesRequest
PatchClusterCustomObjectScale contentType Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
PatchClusterCustomObjectScale contentType Value 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
PatchClusterCustomObjectScale contentType Value accept
-> Body
-> KubernetesRequest
PatchClusterCustomObjectScale contentType Value 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` Body
body
data PatchClusterCustomObjectScale
instance HasBodyParam PatchClusterCustomObjectScale Body
instance HasOptionalParam PatchClusterCustomObjectScale DryRun where
applyOptionalParam :: KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
-> DryRun
-> KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
applyOptionalParam KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
req KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchClusterCustomObjectScale 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 PatchClusterCustomObjectScale FieldManager where
applyOptionalParam :: KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
-> FieldManager
-> KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
applyOptionalParam KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
req KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam PatchClusterCustomObjectScale Force where
applyOptionalParam :: KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
-> Force
-> KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
applyOptionalParam KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
req (Force Bool
xs) =
KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
req KubernetesRequest
PatchClusterCustomObjectScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchClusterCustomObjectScale 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
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Consumes PatchClusterCustomObjectScale MimeJsonPatchjson
instance Consumes PatchClusterCustomObjectScale MimeMergePatchjson
instance Produces PatchClusterCustomObjectScale MimeJSON
instance Produces PatchClusterCustomObjectScale MimeVndKubernetesProtobuf
instance Produces PatchClusterCustomObjectScale MimeYaml
patchClusterCustomObjectStatus
:: (Consumes PatchClusterCustomObjectStatus contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest PatchClusterCustomObjectStatus contentType A.Value accept
patchClusterCustomObjectStatus :: ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest
PatchClusterCustomObjectStatus contentType Value accept
patchClusterCustomObjectStatus ContentType contentType
_ Accept accept
_ Body
body (Group Text
group) (Version Text
version) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
PatchClusterCustomObjectStatus contentType Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
KubernetesRequest
PatchClusterCustomObjectStatus contentType Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
PatchClusterCustomObjectStatus contentType Value 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
PatchClusterCustomObjectStatus contentType Value accept
-> Body
-> KubernetesRequest
PatchClusterCustomObjectStatus contentType Value 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` Body
body
data PatchClusterCustomObjectStatus
instance HasBodyParam PatchClusterCustomObjectStatus Body
instance HasOptionalParam PatchClusterCustomObjectStatus DryRun where
applyOptionalParam :: KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
-> DryRun
-> KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
applyOptionalParam KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
req KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchClusterCustomObjectStatus 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 PatchClusterCustomObjectStatus FieldManager where
applyOptionalParam :: KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
-> FieldManager
-> KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
applyOptionalParam KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
req KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam PatchClusterCustomObjectStatus Force where
applyOptionalParam :: KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
-> Force
-> KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
applyOptionalParam KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
req (Force Bool
xs) =
KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
req KubernetesRequest
PatchClusterCustomObjectStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchClusterCustomObjectStatus 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
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Consumes PatchClusterCustomObjectStatus MimeJsonPatchjson
instance Consumes PatchClusterCustomObjectStatus MimeMergePatchjson
instance Produces PatchClusterCustomObjectStatus MimeJSON
instance Produces PatchClusterCustomObjectStatus MimeVndKubernetesProtobuf
instance Produces PatchClusterCustomObjectStatus MimeYaml
patchNamespacedCustomObject
:: (Consumes PatchNamespacedCustomObject contentType, MimeRender contentType Body)
=> ContentType contentType
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest PatchNamespacedCustomObject contentType A.Value MimeJSON
patchNamespacedCustomObject :: ContentType contentType
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest
PatchNamespacedCustomObject contentType Value MimeJSON
patchNamespacedCustomObject ContentType contentType
_ Body
body (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
PatchNamespacedCustomObject contentType Value MimeJSON
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
PatchNamespacedCustomObject contentType Value MimeJSON
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
PatchNamespacedCustomObject contentType Value MimeJSON
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
PatchNamespacedCustomObject contentType Value MimeJSON
-> Body
-> KubernetesRequest
PatchNamespacedCustomObject contentType Value MimeJSON
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` Body
body
data PatchNamespacedCustomObject
instance HasBodyParam PatchNamespacedCustomObject Body
instance HasOptionalParam PatchNamespacedCustomObject DryRun where
applyOptionalParam :: KubernetesRequest
PatchNamespacedCustomObject contentType res accept
-> DryRun
-> KubernetesRequest
PatchNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
PatchNamespacedCustomObject contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
PatchNamespacedCustomObject contentType res accept
req KubernetesRequest
PatchNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchNamespacedCustomObject 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 PatchNamespacedCustomObject FieldManager where
applyOptionalParam :: KubernetesRequest
PatchNamespacedCustomObject contentType res accept
-> FieldManager
-> KubernetesRequest
PatchNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
PatchNamespacedCustomObject contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
PatchNamespacedCustomObject contentType res accept
req KubernetesRequest
PatchNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchNamespacedCustomObject contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam PatchNamespacedCustomObject Force where
applyOptionalParam :: KubernetesRequest
PatchNamespacedCustomObject contentType res accept
-> Force
-> KubernetesRequest
PatchNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
PatchNamespacedCustomObject contentType res accept
req (Force Bool
xs) =
KubernetesRequest
PatchNamespacedCustomObject contentType res accept
req KubernetesRequest
PatchNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchNamespacedCustomObject 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
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Consumes PatchNamespacedCustomObject MimeJsonPatchjson
instance Consumes PatchNamespacedCustomObject MimeMergePatchjson
instance Produces PatchNamespacedCustomObject MimeJSON
patchNamespacedCustomObjectScale
:: (Consumes PatchNamespacedCustomObjectScale contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest PatchNamespacedCustomObjectScale contentType A.Value accept
patchNamespacedCustomObjectScale :: ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest
PatchNamespacedCustomObjectScale contentType Value accept
patchNamespacedCustomObjectScale ContentType contentType
_ Accept accept
_ Body
body (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
PatchNamespacedCustomObjectScale contentType Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/scale"]
KubernetesRequest
PatchNamespacedCustomObjectScale contentType Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
PatchNamespacedCustomObjectScale contentType Value 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
PatchNamespacedCustomObjectScale contentType Value accept
-> Body
-> KubernetesRequest
PatchNamespacedCustomObjectScale contentType Value 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` Body
body
data PatchNamespacedCustomObjectScale
instance HasBodyParam PatchNamespacedCustomObjectScale Body
instance HasOptionalParam PatchNamespacedCustomObjectScale DryRun where
applyOptionalParam :: KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
-> DryRun
-> KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
applyOptionalParam KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
req KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchNamespacedCustomObjectScale 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 PatchNamespacedCustomObjectScale FieldManager where
applyOptionalParam :: KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
-> FieldManager
-> KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
applyOptionalParam KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
req KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam PatchNamespacedCustomObjectScale Force where
applyOptionalParam :: KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
-> Force
-> KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
applyOptionalParam KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
req (Force Bool
xs) =
KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
req KubernetesRequest
PatchNamespacedCustomObjectScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchNamespacedCustomObjectScale 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
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Consumes PatchNamespacedCustomObjectScale MimeApplyPatchyaml
instance Consumes PatchNamespacedCustomObjectScale MimeJsonPatchjson
instance Consumes PatchNamespacedCustomObjectScale MimeMergePatchjson
instance Produces PatchNamespacedCustomObjectScale MimeJSON
instance Produces PatchNamespacedCustomObjectScale MimeVndKubernetesProtobuf
instance Produces PatchNamespacedCustomObjectScale MimeYaml
patchNamespacedCustomObjectStatus
:: (Consumes PatchNamespacedCustomObjectStatus contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest PatchNamespacedCustomObjectStatus contentType A.Value accept
patchNamespacedCustomObjectStatus :: ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest
PatchNamespacedCustomObjectStatus contentType Value accept
patchNamespacedCustomObjectStatus ContentType contentType
_ Accept accept
_ Body
body (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
PatchNamespacedCustomObjectStatus contentType Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
KubernetesRequest
PatchNamespacedCustomObjectStatus contentType Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
PatchNamespacedCustomObjectStatus contentType Value 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
PatchNamespacedCustomObjectStatus contentType Value accept
-> Body
-> KubernetesRequest
PatchNamespacedCustomObjectStatus contentType Value 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` Body
body
data PatchNamespacedCustomObjectStatus
instance HasBodyParam PatchNamespacedCustomObjectStatus Body
instance HasOptionalParam PatchNamespacedCustomObjectStatus DryRun where
applyOptionalParam :: KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
-> DryRun
-> KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
applyOptionalParam KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
req KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchNamespacedCustomObjectStatus 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 PatchNamespacedCustomObjectStatus FieldManager where
applyOptionalParam :: KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
-> FieldManager
-> KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
applyOptionalParam KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
req KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"fieldManager", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)
instance HasOptionalParam PatchNamespacedCustomObjectStatus Force where
applyOptionalParam :: KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
-> Force
-> KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
applyOptionalParam KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
req (Force Bool
xs) =
KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
req KubernetesRequest
PatchNamespacedCustomObjectStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
PatchNamespacedCustomObjectStatus 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
"force", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)
instance Consumes PatchNamespacedCustomObjectStatus MimeApplyPatchyaml
instance Consumes PatchNamespacedCustomObjectStatus MimeJsonPatchjson
instance Consumes PatchNamespacedCustomObjectStatus MimeMergePatchjson
instance Produces PatchNamespacedCustomObjectStatus MimeJSON
instance Produces PatchNamespacedCustomObjectStatus MimeVndKubernetesProtobuf
instance Produces PatchNamespacedCustomObjectStatus MimeYaml
replaceClusterCustomObject
:: (Consumes ReplaceClusterCustomObject contentType, MimeRender contentType Body)
=> ContentType contentType
-> Body
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest ReplaceClusterCustomObject contentType A.Value MimeJSON
replaceClusterCustomObject :: ContentType contentType
-> Body
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest
ReplaceClusterCustomObject contentType Value MimeJSON
replaceClusterCustomObject ContentType contentType
_ Body
body (Group Text
group) (Version Text
version) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReplaceClusterCustomObject contentType Value MimeJSON
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
ReplaceClusterCustomObject contentType Value MimeJSON
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReplaceClusterCustomObject contentType Value MimeJSON
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
ReplaceClusterCustomObject contentType Value MimeJSON
-> Body
-> KubernetesRequest
ReplaceClusterCustomObject contentType Value MimeJSON
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` Body
body
data ReplaceClusterCustomObject
instance HasBodyParam ReplaceClusterCustomObject Body
instance HasOptionalParam ReplaceClusterCustomObject DryRun where
applyOptionalParam :: KubernetesRequest ReplaceClusterCustomObject contentType res accept
-> DryRun
-> KubernetesRequest
ReplaceClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest ReplaceClusterCustomObject contentType res accept
req (DryRun Text
xs) =
KubernetesRequest ReplaceClusterCustomObject contentType res accept
req KubernetesRequest ReplaceClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
ReplaceClusterCustomObject 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 ReplaceClusterCustomObject FieldManager where
applyOptionalParam :: KubernetesRequest ReplaceClusterCustomObject contentType res accept
-> FieldManager
-> KubernetesRequest
ReplaceClusterCustomObject contentType res accept
applyOptionalParam KubernetesRequest ReplaceClusterCustomObject contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest ReplaceClusterCustomObject contentType res accept
req KubernetesRequest ReplaceClusterCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
ReplaceClusterCustomObject 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 ReplaceClusterCustomObject mtype
instance Produces ReplaceClusterCustomObject MimeJSON
replaceClusterCustomObjectScale
:: (Consumes ReplaceClusterCustomObjectScale contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest ReplaceClusterCustomObjectScale contentType A.Value accept
replaceClusterCustomObjectScale :: ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest
ReplaceClusterCustomObjectScale contentType Value accept
replaceClusterCustomObjectScale ContentType contentType
_ Accept accept
_ Body
body (Group Text
group) (Version Text
version) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReplaceClusterCustomObjectScale contentType Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/scale"]
KubernetesRequest
ReplaceClusterCustomObjectScale contentType Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReplaceClusterCustomObjectScale contentType Value 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
ReplaceClusterCustomObjectScale contentType Value accept
-> Body
-> KubernetesRequest
ReplaceClusterCustomObjectScale contentType Value 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` Body
body
data ReplaceClusterCustomObjectScale
instance HasBodyParam ReplaceClusterCustomObjectScale Body
instance HasOptionalParam ReplaceClusterCustomObjectScale DryRun where
applyOptionalParam :: KubernetesRequest
ReplaceClusterCustomObjectScale contentType res accept
-> DryRun
-> KubernetesRequest
ReplaceClusterCustomObjectScale contentType res accept
applyOptionalParam KubernetesRequest
ReplaceClusterCustomObjectScale contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
ReplaceClusterCustomObjectScale contentType res accept
req KubernetesRequest
ReplaceClusterCustomObjectScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
ReplaceClusterCustomObjectScale 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 ReplaceClusterCustomObjectScale FieldManager where
applyOptionalParam :: KubernetesRequest
ReplaceClusterCustomObjectScale contentType res accept
-> FieldManager
-> KubernetesRequest
ReplaceClusterCustomObjectScale contentType res accept
applyOptionalParam KubernetesRequest
ReplaceClusterCustomObjectScale contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
ReplaceClusterCustomObjectScale contentType res accept
req KubernetesRequest
ReplaceClusterCustomObjectScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
ReplaceClusterCustomObjectScale 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 ReplaceClusterCustomObjectScale mtype
instance Produces ReplaceClusterCustomObjectScale MimeJSON
instance Produces ReplaceClusterCustomObjectScale MimeVndKubernetesProtobuf
instance Produces ReplaceClusterCustomObjectScale MimeYaml
replaceClusterCustomObjectStatus
:: (Consumes ReplaceClusterCustomObjectStatus contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest ReplaceClusterCustomObjectStatus contentType A.Value accept
replaceClusterCustomObjectStatus :: ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Plural
-> Name
-> KubernetesRequest
ReplaceClusterCustomObjectStatus contentType Value accept
replaceClusterCustomObjectStatus ContentType contentType
_ Accept accept
_ Body
body (Group Text
group) (Version Text
version) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReplaceClusterCustomObjectStatus contentType Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
KubernetesRequest
ReplaceClusterCustomObjectStatus contentType Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReplaceClusterCustomObjectStatus contentType Value 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
ReplaceClusterCustomObjectStatus contentType Value accept
-> Body
-> KubernetesRequest
ReplaceClusterCustomObjectStatus contentType Value 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` Body
body
data ReplaceClusterCustomObjectStatus
instance HasBodyParam ReplaceClusterCustomObjectStatus Body
instance HasOptionalParam ReplaceClusterCustomObjectStatus DryRun where
applyOptionalParam :: KubernetesRequest
ReplaceClusterCustomObjectStatus contentType res accept
-> DryRun
-> KubernetesRequest
ReplaceClusterCustomObjectStatus contentType res accept
applyOptionalParam KubernetesRequest
ReplaceClusterCustomObjectStatus contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
ReplaceClusterCustomObjectStatus contentType res accept
req KubernetesRequest
ReplaceClusterCustomObjectStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
ReplaceClusterCustomObjectStatus 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 ReplaceClusterCustomObjectStatus FieldManager where
applyOptionalParam :: KubernetesRequest
ReplaceClusterCustomObjectStatus contentType res accept
-> FieldManager
-> KubernetesRequest
ReplaceClusterCustomObjectStatus contentType res accept
applyOptionalParam KubernetesRequest
ReplaceClusterCustomObjectStatus contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
ReplaceClusterCustomObjectStatus contentType res accept
req KubernetesRequest
ReplaceClusterCustomObjectStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
ReplaceClusterCustomObjectStatus 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 ReplaceClusterCustomObjectStatus mtype
instance Produces ReplaceClusterCustomObjectStatus MimeJSON
instance Produces ReplaceClusterCustomObjectStatus MimeVndKubernetesProtobuf
instance Produces ReplaceClusterCustomObjectStatus MimeYaml
replaceNamespacedCustomObject
:: (Consumes ReplaceNamespacedCustomObject contentType, MimeRender contentType Body)
=> ContentType contentType
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest ReplaceNamespacedCustomObject contentType A.Value MimeJSON
replaceNamespacedCustomObject :: ContentType contentType
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest
ReplaceNamespacedCustomObject contentType Value MimeJSON
replaceNamespacedCustomObject ContentType contentType
_ Body
body (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReplaceNamespacedCustomObject contentType Value MimeJSON
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
KubernetesRequest
ReplaceNamespacedCustomObject contentType Value MimeJSON
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReplaceNamespacedCustomObject contentType Value MimeJSON
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
ReplaceNamespacedCustomObject contentType Value MimeJSON
-> Body
-> KubernetesRequest
ReplaceNamespacedCustomObject contentType Value MimeJSON
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` Body
body
data ReplaceNamespacedCustomObject
instance HasBodyParam ReplaceNamespacedCustomObject Body
instance HasOptionalParam ReplaceNamespacedCustomObject DryRun where
applyOptionalParam :: KubernetesRequest
ReplaceNamespacedCustomObject contentType res accept
-> DryRun
-> KubernetesRequest
ReplaceNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
ReplaceNamespacedCustomObject contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
ReplaceNamespacedCustomObject contentType res accept
req KubernetesRequest
ReplaceNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
ReplaceNamespacedCustomObject 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 ReplaceNamespacedCustomObject FieldManager where
applyOptionalParam :: KubernetesRequest
ReplaceNamespacedCustomObject contentType res accept
-> FieldManager
-> KubernetesRequest
ReplaceNamespacedCustomObject contentType res accept
applyOptionalParam KubernetesRequest
ReplaceNamespacedCustomObject contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
ReplaceNamespacedCustomObject contentType res accept
req KubernetesRequest
ReplaceNamespacedCustomObject contentType res accept
-> [QueryItem]
-> KubernetesRequest
ReplaceNamespacedCustomObject 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 ReplaceNamespacedCustomObject mtype
instance Produces ReplaceNamespacedCustomObject MimeJSON
replaceNamespacedCustomObjectScale
:: (Consumes ReplaceNamespacedCustomObjectScale contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest ReplaceNamespacedCustomObjectScale contentType A.Value accept
replaceNamespacedCustomObjectScale :: ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType Value accept
replaceNamespacedCustomObjectScale ContentType contentType
_ Accept accept
_ Body
body (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/scale"]
KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType Value 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
ReplaceNamespacedCustomObjectScale contentType Value accept
-> Body
-> KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType Value 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` Body
body
data ReplaceNamespacedCustomObjectScale
instance HasBodyParam ReplaceNamespacedCustomObjectScale Body
instance HasOptionalParam ReplaceNamespacedCustomObjectScale DryRun where
applyOptionalParam :: KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType res accept
-> DryRun
-> KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType res accept
applyOptionalParam KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType res accept
req KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
ReplaceNamespacedCustomObjectScale 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 ReplaceNamespacedCustomObjectScale FieldManager where
applyOptionalParam :: KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType res accept
-> FieldManager
-> KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType res accept
applyOptionalParam KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType res accept
req KubernetesRequest
ReplaceNamespacedCustomObjectScale contentType res accept
-> [QueryItem]
-> KubernetesRequest
ReplaceNamespacedCustomObjectScale 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 ReplaceNamespacedCustomObjectScale mtype
instance Produces ReplaceNamespacedCustomObjectScale MimeJSON
instance Produces ReplaceNamespacedCustomObjectScale MimeVndKubernetesProtobuf
instance Produces ReplaceNamespacedCustomObjectScale MimeYaml
replaceNamespacedCustomObjectStatus
:: (Consumes ReplaceNamespacedCustomObjectStatus contentType, MimeRender contentType Body)
=> ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest ReplaceNamespacedCustomObjectStatus contentType A.Value accept
replaceNamespacedCustomObjectStatus :: ContentType contentType
-> Accept accept
-> Body
-> Group
-> Version
-> Namespace
-> Plural
-> Name
-> KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType Value accept
replaceNamespacedCustomObjectStatus ContentType contentType
_ Accept accept
_ Body
body (Group Text
group) (Version Text
version) (Namespace Text
namespace) (Plural Text
plural) (Name Text
name) =
Method
-> [ByteString]
-> KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType Value accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
group,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
version,ByteString
"/namespaces/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
namespace,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
plural,ByteString
"/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType Value accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType Value 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
ReplaceNamespacedCustomObjectStatus contentType Value accept
-> Body
-> KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType Value 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` Body
body
data ReplaceNamespacedCustomObjectStatus
instance HasBodyParam ReplaceNamespacedCustomObjectStatus Body
instance HasOptionalParam ReplaceNamespacedCustomObjectStatus DryRun where
applyOptionalParam :: KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType res accept
-> DryRun
-> KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType res accept
applyOptionalParam KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType res accept
req (DryRun Text
xs) =
KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType res accept
req KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
ReplaceNamespacedCustomObjectStatus 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 ReplaceNamespacedCustomObjectStatus FieldManager where
applyOptionalParam :: KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType res accept
-> FieldManager
-> KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType res accept
applyOptionalParam KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType res accept
req (FieldManager Text
xs) =
KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType res accept
req KubernetesRequest
ReplaceNamespacedCustomObjectStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
ReplaceNamespacedCustomObjectStatus 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 ReplaceNamespacedCustomObjectStatus mtype
instance Produces ReplaceNamespacedCustomObjectStatus MimeJSON
instance Produces ReplaceNamespacedCustomObjectStatus MimeVndKubernetesProtobuf
instance Produces ReplaceNamespacedCustomObjectStatus MimeYaml