{-
   Kubernetes

   No description provided (generated by Openapi Generator https://github.com/openapitools/openapi-generator)

   OpenAPI Version: 3.0.1
   Kubernetes API version: release-1.32
   Generated by OpenAPI Generator (https://openapi-generator.tech)
-}

{-|
Module : Kubernetes.OpenAPI.API.NetworkingV1beta1
-}

{-# 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.NetworkingV1beta1 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

-- * Operations


-- ** NetworkingV1beta1

-- *** createIPAddress

-- | @POST \/apis\/networking.k8s.io\/v1beta1\/ipaddresses@
-- 
-- create an IPAddress
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createIPAddress
  :: (Consumes CreateIPAddress contentType, MimeRender contentType V1beta1IPAddress)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1beta1IPAddress -- ^ "body"
  -> KubernetesRequest CreateIPAddress contentType V1beta1IPAddress accept
createIPAddress :: forall contentType accept.
(Consumes CreateIPAddress contentType,
 MimeRender contentType V1beta1IPAddress) =>
ContentType contentType
-> Accept accept
-> V1beta1IPAddress
-> KubernetesRequest
     CreateIPAddress contentType V1beta1IPAddress accept
createIPAddress ContentType contentType
_  Accept accept
_ V1beta1IPAddress
body =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateIPAddress contentType V1beta1IPAddress accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/networking.k8s.io/v1beta1/ipaddresses"]
    KubernetesRequest
  CreateIPAddress contentType V1beta1IPAddress accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateIPAddress contentType V1beta1IPAddress 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
  CreateIPAddress contentType V1beta1IPAddress accept
-> V1beta1IPAddress
-> KubernetesRequest
     CreateIPAddress contentType V1beta1IPAddress 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
forall contentType res accept.
(Consumes CreateIPAddress contentType,
 MimeRender contentType V1beta1IPAddress) =>
KubernetesRequest CreateIPAddress contentType res accept
-> V1beta1IPAddress
-> KubernetesRequest CreateIPAddress contentType res accept
`setBodyParam` V1beta1IPAddress
body

data CreateIPAddress 
instance HasBodyParam CreateIPAddress V1beta1IPAddress 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateIPAddress Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateIPAddress contentType res accept
-> Pretty
-> KubernetesRequest CreateIPAddress contentType res accept
applyOptionalParam KubernetesRequest CreateIPAddress contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateIPAddress contentType res accept
req KubernetesRequest CreateIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateIPAddress 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)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateIPAddress DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateIPAddress contentType res accept
-> DryRun
-> KubernetesRequest CreateIPAddress contentType res accept
applyOptionalParam KubernetesRequest CreateIPAddress contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateIPAddress contentType res accept
req KubernetesRequest CreateIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateIPAddress 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)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateIPAddress FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateIPAddress contentType res accept
-> FieldManager
-> KubernetesRequest CreateIPAddress contentType res accept
applyOptionalParam KubernetesRequest CreateIPAddress contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateIPAddress contentType res accept
req KubernetesRequest CreateIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateIPAddress 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)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateIPAddress FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateIPAddress contentType res accept
-> FieldValidation
-> KubernetesRequest CreateIPAddress contentType res accept
applyOptionalParam KubernetesRequest CreateIPAddress contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateIPAddress contentType res accept
req KubernetesRequest CreateIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateIPAddress 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
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateIPAddress mtype

-- | @application/json@
instance Produces CreateIPAddress MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateIPAddress MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateIPAddress MimeCbor
-- | @application/yaml@
instance Produces CreateIPAddress MimeYaml


-- *** createServiceCIDR

-- | @POST \/apis\/networking.k8s.io\/v1beta1\/servicecidrs@
-- 
-- create a ServiceCIDR
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
createServiceCIDR
  :: (Consumes CreateServiceCIDR contentType, MimeRender contentType V1beta1ServiceCIDR)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1beta1ServiceCIDR -- ^ "body"
  -> KubernetesRequest CreateServiceCIDR contentType V1beta1ServiceCIDR accept
createServiceCIDR :: forall contentType accept.
(Consumes CreateServiceCIDR contentType,
 MimeRender contentType V1beta1ServiceCIDR) =>
ContentType contentType
-> Accept accept
-> V1beta1ServiceCIDR
-> KubernetesRequest
     CreateServiceCIDR contentType V1beta1ServiceCIDR accept
createServiceCIDR ContentType contentType
_  Accept accept
_ V1beta1ServiceCIDR
body =
  Method
-> [ByteString]
-> KubernetesRequest
     CreateServiceCIDR contentType V1beta1ServiceCIDR accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/apis/networking.k8s.io/v1beta1/servicecidrs"]
    KubernetesRequest
  CreateServiceCIDR contentType V1beta1ServiceCIDR accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     CreateServiceCIDR contentType V1beta1ServiceCIDR 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
  CreateServiceCIDR contentType V1beta1ServiceCIDR accept
-> V1beta1ServiceCIDR
-> KubernetesRequest
     CreateServiceCIDR contentType V1beta1ServiceCIDR 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
forall contentType res accept.
(Consumes CreateServiceCIDR contentType,
 MimeRender contentType V1beta1ServiceCIDR) =>
KubernetesRequest CreateServiceCIDR contentType res accept
-> V1beta1ServiceCIDR
-> KubernetesRequest CreateServiceCIDR contentType res accept
`setBodyParam` V1beta1ServiceCIDR
body

data CreateServiceCIDR 
instance HasBodyParam CreateServiceCIDR V1beta1ServiceCIDR 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam CreateServiceCIDR Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateServiceCIDR contentType res accept
-> Pretty
-> KubernetesRequest CreateServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest CreateServiceCIDR contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest CreateServiceCIDR contentType res accept
req KubernetesRequest CreateServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateServiceCIDR 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)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam CreateServiceCIDR DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateServiceCIDR contentType res accept
-> DryRun
-> KubernetesRequest CreateServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest CreateServiceCIDR contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest CreateServiceCIDR contentType res accept
req KubernetesRequest CreateServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateServiceCIDR 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)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam CreateServiceCIDR FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateServiceCIDR contentType res accept
-> FieldManager
-> KubernetesRequest CreateServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest CreateServiceCIDR contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest CreateServiceCIDR contentType res accept
req KubernetesRequest CreateServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateServiceCIDR 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)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam CreateServiceCIDR FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest CreateServiceCIDR contentType res accept
-> FieldValidation
-> KubernetesRequest CreateServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest CreateServiceCIDR contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest CreateServiceCIDR contentType res accept
req KubernetesRequest CreateServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest CreateServiceCIDR 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
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes CreateServiceCIDR mtype

-- | @application/json@
instance Produces CreateServiceCIDR MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces CreateServiceCIDR MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces CreateServiceCIDR MimeCbor
-- | @application/yaml@
instance Produces CreateServiceCIDR MimeYaml


-- *** deleteCollectionIPAddress

-- | @DELETE \/apis\/networking.k8s.io\/v1beta1\/ipaddresses@
-- 
-- delete collection of IPAddress
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionIPAddress
  :: (Consumes DeleteCollectionIPAddress contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest DeleteCollectionIPAddress contentType V1Status accept
deleteCollectionIPAddress :: forall contentType accept.
Consumes DeleteCollectionIPAddress contentType =>
ContentType contentType
-> Accept accept
-> KubernetesRequest
     DeleteCollectionIPAddress contentType V1Status accept
deleteCollectionIPAddress ContentType contentType
_  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionIPAddress contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/networking.k8s.io/v1beta1/ipaddresses"]
    KubernetesRequest
  DeleteCollectionIPAddress contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionIPAddress contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionIPAddress 
instance HasBodyParam DeleteCollectionIPAddress V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionIPAddress Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionIPAddress Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (Continue Text
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionIPAddress DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionIPAddress FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionIPAddress GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionIPAddress IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionIPAddress LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionIPAddress Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (Limit Int
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionIPAddress OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionIPAddress PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionIPAddress ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionIPAddress ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionIPAddress SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress 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
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionIPAddress TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteCollectionIPAddress contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest DeleteCollectionIPAddress contentType res accept
req KubernetesRequest DeleteCollectionIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionIPAddress contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionIPAddress mtype

-- | @application/json@
instance Produces DeleteCollectionIPAddress MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionIPAddress MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionIPAddress MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionIPAddress MimeYaml


-- *** deleteCollectionServiceCIDR

-- | @DELETE \/apis\/networking.k8s.io\/v1beta1\/servicecidrs@
-- 
-- delete collection of ServiceCIDR
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteCollectionServiceCIDR
  :: (Consumes DeleteCollectionServiceCIDR contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest DeleteCollectionServiceCIDR contentType V1Status accept
deleteCollectionServiceCIDR :: forall contentType accept.
Consumes DeleteCollectionServiceCIDR contentType =>
ContentType contentType
-> Accept accept
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType V1Status accept
deleteCollectionServiceCIDR ContentType contentType
_  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/networking.k8s.io/v1beta1/servicecidrs"]
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteCollectionServiceCIDR 
instance HasBodyParam DeleteCollectionServiceCIDR V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteCollectionServiceCIDR Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> Pretty
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam DeleteCollectionServiceCIDR Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> Continue
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (Continue Text
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteCollectionServiceCIDR DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> DryRun
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam DeleteCollectionServiceCIDR FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> FieldSelector
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteCollectionServiceCIDR GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteCollectionServiceCIDR IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam DeleteCollectionServiceCIDR LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> LabelSelector
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam DeleteCollectionServiceCIDR Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> Limit
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (Limit Int
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteCollectionServiceCIDR OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> OrphanDependents
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteCollectionServiceCIDR PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> PropagationPolicy
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionServiceCIDR ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> ResourceVersion
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam DeleteCollectionServiceCIDR ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam DeleteCollectionServiceCIDR SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> SendInitialEvents
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR 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
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam DeleteCollectionServiceCIDR TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> TimeoutSeconds
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
req KubernetesRequest
  DeleteCollectionServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest
     DeleteCollectionServiceCIDR contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Int) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"timeoutSeconds", Int -> Maybe Int
forall a. a -> Maybe a
Just Int
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteCollectionServiceCIDR mtype

-- | @application/json@
instance Produces DeleteCollectionServiceCIDR MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteCollectionServiceCIDR MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteCollectionServiceCIDR MimeCbor
-- | @application/yaml@
instance Produces DeleteCollectionServiceCIDR MimeYaml


-- *** deleteIPAddress

-- | @DELETE \/apis\/networking.k8s.io\/v1beta1\/ipaddresses\/{name}@
-- 
-- delete an IPAddress
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteIPAddress
  :: (Consumes DeleteIPAddress contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the IPAddress
  -> KubernetesRequest DeleteIPAddress contentType V1Status accept
deleteIPAddress :: forall contentType accept.
Consumes DeleteIPAddress contentType =>
ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest DeleteIPAddress contentType V1Status accept
deleteIPAddress ContentType contentType
_  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest DeleteIPAddress contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/networking.k8s.io/v1beta1/ipaddresses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest DeleteIPAddress contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest DeleteIPAddress contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteIPAddress 
instance HasBodyParam DeleteIPAddress V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteIPAddress Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteIPAddress contentType res accept
-> Pretty
-> KubernetesRequest DeleteIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteIPAddress contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteIPAddress contentType res accept
req KubernetesRequest DeleteIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteIPAddress 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)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteIPAddress DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteIPAddress contentType res accept
-> DryRun
-> KubernetesRequest DeleteIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteIPAddress contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteIPAddress contentType res accept
req KubernetesRequest DeleteIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteIPAddress 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)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteIPAddress GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteIPAddress contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteIPAddress contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteIPAddress contentType res accept
req KubernetesRequest DeleteIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteIPAddress 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)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteIPAddress IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteIPAddress contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest DeleteIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteIPAddress contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteIPAddress contentType res accept
req KubernetesRequest DeleteIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteIPAddress 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
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteIPAddress OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteIPAddress contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteIPAddress contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteIPAddress contentType res accept
req KubernetesRequest DeleteIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteIPAddress 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)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteIPAddress PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteIPAddress contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteIPAddress contentType res accept
applyOptionalParam KubernetesRequest DeleteIPAddress contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteIPAddress contentType res accept
req KubernetesRequest DeleteIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteIPAddress contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteIPAddress mtype

-- | @application/json@
instance Produces DeleteIPAddress MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteIPAddress MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteIPAddress MimeCbor
-- | @application/yaml@
instance Produces DeleteIPAddress MimeYaml


-- *** deleteServiceCIDR

-- | @DELETE \/apis\/networking.k8s.io\/v1beta1\/servicecidrs\/{name}@
-- 
-- delete a ServiceCIDR
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
deleteServiceCIDR
  :: (Consumes DeleteServiceCIDR contentType)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceCIDR
  -> KubernetesRequest DeleteServiceCIDR contentType V1Status accept
deleteServiceCIDR :: forall contentType accept.
Consumes DeleteServiceCIDR contentType =>
ContentType contentType
-> Accept accept
-> Name
-> KubernetesRequest DeleteServiceCIDR contentType V1Status accept
deleteServiceCIDR ContentType contentType
_  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest DeleteServiceCIDR contentType V1Status accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/apis/networking.k8s.io/v1beta1/servicecidrs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest DeleteServiceCIDR contentType V1Status accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest DeleteServiceCIDR contentType V1Status accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data DeleteServiceCIDR 
instance HasBodyParam DeleteServiceCIDR V1DeleteOptions 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam DeleteServiceCIDR Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteServiceCIDR contentType res accept
-> Pretty
-> KubernetesRequest DeleteServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest DeleteServiceCIDR contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest DeleteServiceCIDR contentType res accept
req KubernetesRequest DeleteServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteServiceCIDR 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)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam DeleteServiceCIDR DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteServiceCIDR contentType res accept
-> DryRun
-> KubernetesRequest DeleteServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest DeleteServiceCIDR contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest DeleteServiceCIDR contentType res accept
req KubernetesRequest DeleteServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteServiceCIDR 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)

-- | /Optional Param/ "gracePeriodSeconds" - The duration in seconds before the object should be deleted. Value must be non-negative integer. The value zero indicates delete immediately. If this value is nil, the default grace period for the specified type will be used. Defaults to a per object value if not specified. zero means delete immediately.
instance HasOptionalParam DeleteServiceCIDR GracePeriodSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteServiceCIDR contentType res accept
-> GracePeriodSeconds
-> KubernetesRequest DeleteServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest DeleteServiceCIDR contentType res accept
req (GracePeriodSeconds Int
xs) =
    KubernetesRequest DeleteServiceCIDR contentType res accept
req KubernetesRequest DeleteServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteServiceCIDR 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)

-- | /Optional Param/ "ignoreStoreReadErrorWithClusterBreakingPotential" - if set to true, it will trigger an unsafe deletion of the resource in case the normal deletion flow fails with a corrupt object error. A resource is considered corrupt if it can not be retrieved from the underlying storage successfully because of a) its data can not be transformed e.g. decryption failure, or b) it fails to decode into an object. NOTE: unsafe deletion ignores finalizer constraints, skips precondition checks, and removes the object from the storage. WARNING: This may potentially break the cluster if the workload associated with the resource being unsafe-deleted relies on normal deletion flow. Use only if you REALLY know what you are doing. The default value is false, and the user must opt in to enable it
instance HasOptionalParam DeleteServiceCIDR IgnoreStoreReadErrorWithClusterBreakingPotential where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteServiceCIDR contentType res accept
-> IgnoreStoreReadErrorWithClusterBreakingPotential
-> KubernetesRequest DeleteServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest DeleteServiceCIDR contentType res accept
req (IgnoreStoreReadErrorWithClusterBreakingPotential Bool
xs) =
    KubernetesRequest DeleteServiceCIDR contentType res accept
req KubernetesRequest DeleteServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteServiceCIDR 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
"ignoreStoreReadErrorWithClusterBreakingPotential", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If true/false, the \"orphan\" finalizer will be added to/removed from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both.
instance HasOptionalParam DeleteServiceCIDR OrphanDependents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteServiceCIDR contentType res accept
-> OrphanDependents
-> KubernetesRequest DeleteServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest DeleteServiceCIDR contentType res accept
req (OrphanDependents Bool
xs) =
    KubernetesRequest DeleteServiceCIDR contentType res accept
req KubernetesRequest DeleteServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteServiceCIDR 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)

-- | /Optional Param/ "propagationPolicy" - Whether and how garbage collection will be performed. Either this field or OrphanDependents may be set, but not both. The default policy is decided by the existing finalizer set in the metadata.finalizers and the resource-specific default policy. Acceptable values are: 'Orphan' - orphan the dependents; 'Background' - allow the garbage collector to delete the dependents in the background; 'Foreground' - a cascading policy that deletes all dependents in the foreground.
instance HasOptionalParam DeleteServiceCIDR PropagationPolicy where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest DeleteServiceCIDR contentType res accept
-> PropagationPolicy
-> KubernetesRequest DeleteServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest DeleteServiceCIDR contentType res accept
req (PropagationPolicy Text
xs) =
    KubernetesRequest DeleteServiceCIDR contentType res accept
req KubernetesRequest DeleteServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest DeleteServiceCIDR contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Text) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"propagationPolicy", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes DeleteServiceCIDR mtype

-- | @application/json@
instance Produces DeleteServiceCIDR MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces DeleteServiceCIDR MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces DeleteServiceCIDR MimeCbor
-- | @application/yaml@
instance Produces DeleteServiceCIDR MimeYaml


-- *** getAPIResources

-- | @GET \/apis\/networking.k8s.io\/v1beta1\/@
-- 
-- get available resources
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
getAPIResources
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest GetAPIResources MimeNoContent V1APIResourceList accept
getAPIResources :: forall accept.
Accept accept
-> KubernetesRequest
     GetAPIResources MimeNoContent V1APIResourceList accept
getAPIResources  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     GetAPIResources MimeNoContent V1APIResourceList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/networking.k8s.io/v1beta1/"]
    KubernetesRequest
  GetAPIResources MimeNoContent V1APIResourceList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     GetAPIResources MimeNoContent V1APIResourceList accept
forall authMethod req contentType res accept.
AuthMethod authMethod =>
KubernetesRequest req contentType res accept
-> Proxy authMethod -> KubernetesRequest req contentType res accept
`_hasAuthType` (Proxy AuthApiKeyBearerToken
forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthApiKeyBearerToken)

data GetAPIResources  
-- | @application/json@
instance Produces GetAPIResources MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces GetAPIResources MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces GetAPIResources MimeCbor
-- | @application/yaml@
instance Produces GetAPIResources MimeYaml


-- *** listIPAddress

-- | @GET \/apis\/networking.k8s.io\/v1beta1\/ipaddresses@
-- 
-- list or watch objects of kind IPAddress
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listIPAddress
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListIPAddress MimeNoContent V1beta1IPAddressList accept
listIPAddress :: forall accept.
Accept accept
-> KubernetesRequest
     ListIPAddress MimeNoContent V1beta1IPAddressList accept
listIPAddress  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListIPAddress MimeNoContent V1beta1IPAddressList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/networking.k8s.io/v1beta1/ipaddresses"]
    KubernetesRequest
  ListIPAddress MimeNoContent V1beta1IPAddressList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListIPAddress MimeNoContent V1beta1IPAddressList 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 ListIPAddress  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListIPAddress Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListIPAddress contentType res accept
-> Pretty -> KubernetesRequest ListIPAddress contentType res accept
applyOptionalParam KubernetesRequest ListIPAddress contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListIPAddress contentType res accept
req KubernetesRequest ListIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ListIPAddress 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)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListIPAddress AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListIPAddress contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListIPAddress contentType res accept
applyOptionalParam KubernetesRequest ListIPAddress contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListIPAddress contentType res accept
req KubernetesRequest ListIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ListIPAddress contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListIPAddress Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListIPAddress contentType res accept
-> Continue
-> KubernetesRequest ListIPAddress contentType res accept
applyOptionalParam KubernetesRequest ListIPAddress contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListIPAddress contentType res accept
req KubernetesRequest ListIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ListIPAddress 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)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListIPAddress FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListIPAddress contentType res accept
-> FieldSelector
-> KubernetesRequest ListIPAddress contentType res accept
applyOptionalParam KubernetesRequest ListIPAddress contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListIPAddress contentType res accept
req KubernetesRequest ListIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ListIPAddress 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)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListIPAddress LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListIPAddress contentType res accept
-> LabelSelector
-> KubernetesRequest ListIPAddress contentType res accept
applyOptionalParam KubernetesRequest ListIPAddress contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListIPAddress contentType res accept
req KubernetesRequest ListIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ListIPAddress 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)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListIPAddress Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListIPAddress contentType res accept
-> Limit -> KubernetesRequest ListIPAddress contentType res accept
applyOptionalParam KubernetesRequest ListIPAddress contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListIPAddress contentType res accept
req KubernetesRequest ListIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ListIPAddress 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)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListIPAddress ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListIPAddress contentType res accept
-> ResourceVersion
-> KubernetesRequest ListIPAddress contentType res accept
applyOptionalParam KubernetesRequest ListIPAddress contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListIPAddress contentType res accept
req KubernetesRequest ListIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ListIPAddress 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)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListIPAddress ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListIPAddress contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListIPAddress contentType res accept
applyOptionalParam KubernetesRequest ListIPAddress contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListIPAddress contentType res accept
req KubernetesRequest ListIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ListIPAddress 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
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListIPAddress SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListIPAddress contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListIPAddress contentType res accept
applyOptionalParam KubernetesRequest ListIPAddress contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListIPAddress contentType res accept
req KubernetesRequest ListIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ListIPAddress 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
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListIPAddress TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListIPAddress contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListIPAddress contentType res accept
applyOptionalParam KubernetesRequest ListIPAddress contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListIPAddress contentType res accept
req KubernetesRequest ListIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ListIPAddress 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)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListIPAddress Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListIPAddress contentType res accept
-> Watch -> KubernetesRequest ListIPAddress contentType res accept
applyOptionalParam KubernetesRequest ListIPAddress contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListIPAddress contentType res accept
req KubernetesRequest ListIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ListIPAddress 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)
-- | @application/cbor-seq@
instance Produces ListIPAddress MimeCborSeq
-- | @application/json@
instance Produces ListIPAddress MimeJSON
-- | @application/json;stream=watch@
instance Produces ListIPAddress MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListIPAddress MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListIPAddress MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListIPAddress MimeCbor
-- | @application/yaml@
instance Produces ListIPAddress MimeYaml


-- *** listServiceCIDR

-- | @GET \/apis\/networking.k8s.io\/v1beta1\/servicecidrs@
-- 
-- list or watch objects of kind ServiceCIDR
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
listServiceCIDR
  :: Accept accept -- ^ request accept ('MimeType')
  -> KubernetesRequest ListServiceCIDR MimeNoContent V1beta1ServiceCIDRList accept
listServiceCIDR :: forall accept.
Accept accept
-> KubernetesRequest
     ListServiceCIDR MimeNoContent V1beta1ServiceCIDRList accept
listServiceCIDR  Accept accept
_ =
  Method
-> [ByteString]
-> KubernetesRequest
     ListServiceCIDR MimeNoContent V1beta1ServiceCIDRList accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/networking.k8s.io/v1beta1/servicecidrs"]
    KubernetesRequest
  ListServiceCIDR MimeNoContent V1beta1ServiceCIDRList accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ListServiceCIDR MimeNoContent V1beta1ServiceCIDRList 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 ListServiceCIDR  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ListServiceCIDR Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListServiceCIDR contentType res accept
-> Pretty
-> KubernetesRequest ListServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ListServiceCIDR contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ListServiceCIDR contentType res accept
req KubernetesRequest ListServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ListServiceCIDR 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)

-- | /Optional Param/ "allowWatchBookmarks" - allowWatchBookmarks requests watch events with type \"BOOKMARK\". Servers that do not implement bookmarks may ignore this flag and bookmarks are sent at the server's discretion. Clients should not assume bookmarks are returned at any specific interval, nor may they assume the server will send any BOOKMARK event during a session. If this is not a watch, this field is ignored.
instance HasOptionalParam ListServiceCIDR AllowWatchBookmarks where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListServiceCIDR contentType res accept
-> AllowWatchBookmarks
-> KubernetesRequest ListServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ListServiceCIDR contentType res accept
req (AllowWatchBookmarks Bool
xs) =
    KubernetesRequest ListServiceCIDR contentType res accept
req KubernetesRequest ListServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ListServiceCIDR contentType res accept
forall req contentType res accept.
KubernetesRequest req contentType res accept
-> [QueryItem] -> KubernetesRequest req contentType res accept
`addQuery` (Method, Maybe Bool) -> [QueryItem]
forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"allowWatchBookmarks", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "continue" - The continue option should be set when retrieving more results from the server. Since this value is server defined, clients may only use the continue value from a previous query result with identical query parameters (except for the value of continue) and the server may reject a continue value it does not recognize. If the specified continue value is no longer valid whether due to expiration (generally five to fifteen minutes) or a configuration change on the server, the server will respond with a 410 ResourceExpired error together with a continue token. If the client needs a consistent list, it must restart their list without the continue field. Otherwise, the client may send another list request with the token received with the 410 error, the server will respond with a list starting from the next key, but from the latest snapshot, which is inconsistent from the previous list results - objects that are created, modified, or deleted after the first list request will be included in the response, as long as their keys are after the \"next key\".  This field is not supported when watch is true. Clients may start a watch from the last resourceVersion value returned by the server and not miss any modifications.
instance HasOptionalParam ListServiceCIDR Continue where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListServiceCIDR contentType res accept
-> Continue
-> KubernetesRequest ListServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ListServiceCIDR contentType res accept
req (Continue Text
xs) =
    KubernetesRequest ListServiceCIDR contentType res accept
req KubernetesRequest ListServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ListServiceCIDR 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)

-- | /Optional Param/ "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything.
instance HasOptionalParam ListServiceCIDR FieldSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListServiceCIDR contentType res accept
-> FieldSelector
-> KubernetesRequest ListServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ListServiceCIDR contentType res accept
req (FieldSelector Text
xs) =
    KubernetesRequest ListServiceCIDR contentType res accept
req KubernetesRequest ListServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ListServiceCIDR 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)

-- | /Optional Param/ "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything.
instance HasOptionalParam ListServiceCIDR LabelSelector where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListServiceCIDR contentType res accept
-> LabelSelector
-> KubernetesRequest ListServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ListServiceCIDR contentType res accept
req (LabelSelector Text
xs) =
    KubernetesRequest ListServiceCIDR contentType res accept
req KubernetesRequest ListServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ListServiceCIDR 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)

-- | /Optional Param/ "limit" - limit is a maximum number of responses to return for a list call. If more items exist, the server will set the `continue` field on the list metadata to a value that can be used with the same initial query to retrieve the next set of results. Setting a limit may return fewer than the requested amount of items (up to zero items) in the event all requested objects are filtered out and clients should only use the presence of the continue field to determine whether more results are available. Servers may choose not to support the limit argument and will return all of the available results. If limit is specified and the continue field is empty, clients may assume that no more results are available. This field is not supported if watch is true.  The server guarantees that the objects returned when using continue will be identical to issuing a single list call without a limit - that is, no objects created, modified, or deleted after the first request is issued will be included in any subsequent continued requests. This is sometimes referred to as a consistent snapshot, and ensures that a client that is using limit to receive smaller chunks of a very large result can ensure they see all possible objects. If objects are updated during a chunked list the version of the object that was present at the time the first list result was calculated is returned.
instance HasOptionalParam ListServiceCIDR Limit where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListServiceCIDR contentType res accept
-> Limit
-> KubernetesRequest ListServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ListServiceCIDR contentType res accept
req (Limit Int
xs) =
    KubernetesRequest ListServiceCIDR contentType res accept
req KubernetesRequest ListServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ListServiceCIDR 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)

-- | /Optional Param/ "resourceVersion" - resourceVersion sets a constraint on what resource versions a request may be served from. See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListServiceCIDR ResourceVersion where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListServiceCIDR contentType res accept
-> ResourceVersion
-> KubernetesRequest ListServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ListServiceCIDR contentType res accept
req (ResourceVersion Text
xs) =
    KubernetesRequest ListServiceCIDR contentType res accept
req KubernetesRequest ListServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ListServiceCIDR 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)

-- | /Optional Param/ "resourceVersionMatch" - resourceVersionMatch determines how resourceVersion is applied to list calls. It is highly recommended that resourceVersionMatch be set for list calls where resourceVersion is set See https://kubernetes.io/docs/reference/using-api/api-concepts/#resource-versions for details.  Defaults to unset
instance HasOptionalParam ListServiceCIDR ResourceVersionMatch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListServiceCIDR contentType res accept
-> ResourceVersionMatch
-> KubernetesRequest ListServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ListServiceCIDR contentType res accept
req (ResourceVersionMatch Text
xs) =
    KubernetesRequest ListServiceCIDR contentType res accept
req KubernetesRequest ListServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ListServiceCIDR 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
"resourceVersionMatch", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "sendInitialEvents" - `sendInitialEvents=true` may be set together with `watch=true`. In that case, the watch stream will begin with synthetic events to produce the current state of objects in the collection. Once all such events have been sent, a synthetic \"Bookmark\" event  will be sent. The bookmark will report the ResourceVersion (RV) corresponding to the set of objects, and be marked with `\"k8s.io/initial-events-end\": \"true\"` annotation. Afterwards, the watch stream will proceed as usual, sending watch events corresponding to changes (subsequent to the RV) to objects watched.  When `sendInitialEvents` option is set, we require `resourceVersionMatch` option to also be set. The semantic of the watch request is as following: - `resourceVersionMatch` = NotOlderThan   is interpreted as \"data at least as new as the provided `resourceVersion`\"   and the bookmark event is send when the state is synced   to a `resourceVersion` at least as fresh as the one provided by the ListOptions.   If `resourceVersion` is unset, this is interpreted as \"consistent read\" and the   bookmark event is send when the state is synced at least to the moment   when request started being processed. - `resourceVersionMatch` set to any other value or unset   Invalid error is returned.  Defaults to true if `resourceVersion=\"\"` or `resourceVersion=\"0\"` (for backward compatibility reasons) and to false otherwise.
instance HasOptionalParam ListServiceCIDR SendInitialEvents where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListServiceCIDR contentType res accept
-> SendInitialEvents
-> KubernetesRequest ListServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ListServiceCIDR contentType res accept
req (SendInitialEvents Bool
xs) =
    KubernetesRequest ListServiceCIDR contentType res accept
req KubernetesRequest ListServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ListServiceCIDR 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
"sendInitialEvents", Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
xs)

-- | /Optional Param/ "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity.
instance HasOptionalParam ListServiceCIDR TimeoutSeconds where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListServiceCIDR contentType res accept
-> TimeoutSeconds
-> KubernetesRequest ListServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ListServiceCIDR contentType res accept
req (TimeoutSeconds Int
xs) =
    KubernetesRequest ListServiceCIDR contentType res accept
req KubernetesRequest ListServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ListServiceCIDR 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)

-- | /Optional Param/ "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion.
instance HasOptionalParam ListServiceCIDR Watch where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ListServiceCIDR contentType res accept
-> Watch
-> KubernetesRequest ListServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ListServiceCIDR contentType res accept
req (Watch Bool
xs) =
    KubernetesRequest ListServiceCIDR contentType res accept
req KubernetesRequest ListServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ListServiceCIDR 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)
-- | @application/cbor-seq@
instance Produces ListServiceCIDR MimeCborSeq
-- | @application/json@
instance Produces ListServiceCIDR MimeJSON
-- | @application/json;stream=watch@
instance Produces ListServiceCIDR MimeJsonstreamwatch
-- | @application/vnd.kubernetes.protobuf@
instance Produces ListServiceCIDR MimeVndKubernetesProtobuf
-- | @application/vnd.kubernetes.protobuf;stream=watch@
instance Produces ListServiceCIDR MimeVndKubernetesProtobufstreamwatch
-- | @application/cbor@
instance Produces ListServiceCIDR MimeCbor
-- | @application/yaml@
instance Produces ListServiceCIDR MimeYaml


-- *** patchIPAddress

-- | @PATCH \/apis\/networking.k8s.io\/v1beta1\/ipaddresses\/{name}@
-- 
-- partially update the specified IPAddress
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchIPAddress
  :: (Consumes PatchIPAddress contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the IPAddress
  -> KubernetesRequest PatchIPAddress contentType V1beta1IPAddress accept
patchIPAddress :: forall contentType accept.
(Consumes PatchIPAddress contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
     PatchIPAddress contentType V1beta1IPAddress accept
patchIPAddress ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchIPAddress contentType V1beta1IPAddress accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/networking.k8s.io/v1beta1/ipaddresses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchIPAddress contentType V1beta1IPAddress accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchIPAddress contentType V1beta1IPAddress 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
  PatchIPAddress contentType V1beta1IPAddress accept
-> Body
-> KubernetesRequest
     PatchIPAddress contentType V1beta1IPAddress 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
forall contentType res accept.
(Consumes PatchIPAddress contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchIPAddress contentType res accept
-> Body -> KubernetesRequest PatchIPAddress contentType res accept
`setBodyParam` Body
body

data PatchIPAddress 
instance HasBodyParam PatchIPAddress Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchIPAddress Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchIPAddress contentType res accept
-> Pretty
-> KubernetesRequest PatchIPAddress contentType res accept
applyOptionalParam KubernetesRequest PatchIPAddress contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchIPAddress contentType res accept
req KubernetesRequest PatchIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchIPAddress 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)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchIPAddress DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchIPAddress contentType res accept
-> DryRun
-> KubernetesRequest PatchIPAddress contentType res accept
applyOptionalParam KubernetesRequest PatchIPAddress contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchIPAddress contentType res accept
req KubernetesRequest PatchIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchIPAddress 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)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchIPAddress FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchIPAddress contentType res accept
-> FieldManager
-> KubernetesRequest PatchIPAddress contentType res accept
applyOptionalParam KubernetesRequest PatchIPAddress contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchIPAddress contentType res accept
req KubernetesRequest PatchIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchIPAddress 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)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchIPAddress FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchIPAddress contentType res accept
-> FieldValidation
-> KubernetesRequest PatchIPAddress contentType res accept
applyOptionalParam KubernetesRequest PatchIPAddress contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchIPAddress contentType res accept
req KubernetesRequest PatchIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchIPAddress 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
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchIPAddress Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchIPAddress contentType res accept
-> Force -> KubernetesRequest PatchIPAddress contentType res accept
applyOptionalParam KubernetesRequest PatchIPAddress contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchIPAddress contentType res accept
req KubernetesRequest PatchIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchIPAddress 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)

-- | @application/apply-patch+yaml@
instance Consumes PatchIPAddress MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchIPAddress MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchIPAddress MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchIPAddress MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchIPAddress MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchIPAddress MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchIPAddress MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchIPAddress MimeCbor
-- | @application/yaml@
instance Produces PatchIPAddress MimeYaml


-- *** patchServiceCIDR

-- | @PATCH \/apis\/networking.k8s.io\/v1beta1\/servicecidrs\/{name}@
-- 
-- partially update the specified ServiceCIDR
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchServiceCIDR
  :: (Consumes PatchServiceCIDR contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ServiceCIDR
  -> KubernetesRequest PatchServiceCIDR contentType V1beta1ServiceCIDR accept
patchServiceCIDR :: forall contentType accept.
(Consumes PatchServiceCIDR contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
     PatchServiceCIDR contentType V1beta1ServiceCIDR accept
patchServiceCIDR ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchServiceCIDR contentType V1beta1ServiceCIDR accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/networking.k8s.io/v1beta1/servicecidrs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  PatchServiceCIDR contentType V1beta1ServiceCIDR accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchServiceCIDR contentType V1beta1ServiceCIDR 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
  PatchServiceCIDR contentType V1beta1ServiceCIDR accept
-> Body
-> KubernetesRequest
     PatchServiceCIDR contentType V1beta1ServiceCIDR 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
forall contentType res accept.
(Consumes PatchServiceCIDR contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchServiceCIDR contentType res accept
-> Body
-> KubernetesRequest PatchServiceCIDR contentType res accept
`setBodyParam` Body
body

data PatchServiceCIDR 
instance HasBodyParam PatchServiceCIDR Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchServiceCIDR Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchServiceCIDR contentType res accept
-> Pretty
-> KubernetesRequest PatchServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest PatchServiceCIDR contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchServiceCIDR contentType res accept
req KubernetesRequest PatchServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchServiceCIDR 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)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchServiceCIDR DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchServiceCIDR contentType res accept
-> DryRun
-> KubernetesRequest PatchServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest PatchServiceCIDR contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchServiceCIDR contentType res accept
req KubernetesRequest PatchServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchServiceCIDR 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)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchServiceCIDR FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchServiceCIDR contentType res accept
-> FieldManager
-> KubernetesRequest PatchServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest PatchServiceCIDR contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchServiceCIDR contentType res accept
req KubernetesRequest PatchServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchServiceCIDR 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)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchServiceCIDR FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchServiceCIDR contentType res accept
-> FieldValidation
-> KubernetesRequest PatchServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest PatchServiceCIDR contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchServiceCIDR contentType res accept
req KubernetesRequest PatchServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchServiceCIDR 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
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchServiceCIDR Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchServiceCIDR contentType res accept
-> Force
-> KubernetesRequest PatchServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest PatchServiceCIDR contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchServiceCIDR contentType res accept
req KubernetesRequest PatchServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchServiceCIDR 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)

-- | @application/apply-patch+yaml@
instance Consumes PatchServiceCIDR MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchServiceCIDR MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchServiceCIDR MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchServiceCIDR MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchServiceCIDR MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchServiceCIDR MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchServiceCIDR MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchServiceCIDR MimeCbor
-- | @application/yaml@
instance Produces PatchServiceCIDR MimeYaml


-- *** patchServiceCIDRStatus

-- | @PATCH \/apis\/networking.k8s.io\/v1beta1\/servicecidrs\/{name}\/status@
-- 
-- partially update status of the specified ServiceCIDR
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
patchServiceCIDRStatus
  :: (Consumes PatchServiceCIDRStatus contentType, MimeRender contentType Body)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> Body -- ^ "body"
  -> Name -- ^ "name" -  name of the ServiceCIDR
  -> KubernetesRequest PatchServiceCIDRStatus contentType V1beta1ServiceCIDR accept
patchServiceCIDRStatus :: forall contentType accept.
(Consumes PatchServiceCIDRStatus contentType,
 MimeRender contentType Body) =>
ContentType contentType
-> Accept accept
-> Body
-> Name
-> KubernetesRequest
     PatchServiceCIDRStatus contentType V1beta1ServiceCIDR accept
patchServiceCIDRStatus ContentType contentType
_  Accept accept
_ Body
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     PatchServiceCIDRStatus contentType V1beta1ServiceCIDR accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/apis/networking.k8s.io/v1beta1/servicecidrs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  PatchServiceCIDRStatus contentType V1beta1ServiceCIDR accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     PatchServiceCIDRStatus contentType V1beta1ServiceCIDR 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
  PatchServiceCIDRStatus contentType V1beta1ServiceCIDR accept
-> Body
-> KubernetesRequest
     PatchServiceCIDRStatus contentType V1beta1ServiceCIDR 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
forall contentType res accept.
(Consumes PatchServiceCIDRStatus contentType,
 MimeRender contentType Body) =>
KubernetesRequest PatchServiceCIDRStatus contentType res accept
-> Body
-> KubernetesRequest PatchServiceCIDRStatus contentType res accept
`setBodyParam` Body
body

data PatchServiceCIDRStatus 
instance HasBodyParam PatchServiceCIDRStatus Body 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam PatchServiceCIDRStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchServiceCIDRStatus contentType res accept
-> Pretty
-> KubernetesRequest PatchServiceCIDRStatus contentType res accept
applyOptionalParam KubernetesRequest PatchServiceCIDRStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest PatchServiceCIDRStatus contentType res accept
req KubernetesRequest PatchServiceCIDRStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchServiceCIDRStatus 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)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam PatchServiceCIDRStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchServiceCIDRStatus contentType res accept
-> DryRun
-> KubernetesRequest PatchServiceCIDRStatus contentType res accept
applyOptionalParam KubernetesRequest PatchServiceCIDRStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest PatchServiceCIDRStatus contentType res accept
req KubernetesRequest PatchServiceCIDRStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchServiceCIDRStatus 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)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint. This field is required for apply requests (application/apply-patch) but optional for non-apply patch types (JsonPatch, MergePatch, StrategicMergePatch).
instance HasOptionalParam PatchServiceCIDRStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchServiceCIDRStatus contentType res accept
-> FieldManager
-> KubernetesRequest PatchServiceCIDRStatus contentType res accept
applyOptionalParam KubernetesRequest PatchServiceCIDRStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest PatchServiceCIDRStatus contentType res accept
req KubernetesRequest PatchServiceCIDRStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchServiceCIDRStatus 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)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam PatchServiceCIDRStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchServiceCIDRStatus contentType res accept
-> FieldValidation
-> KubernetesRequest PatchServiceCIDRStatus contentType res accept
applyOptionalParam KubernetesRequest PatchServiceCIDRStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest PatchServiceCIDRStatus contentType res accept
req KubernetesRequest PatchServiceCIDRStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchServiceCIDRStatus 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
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "force" - Force is going to \"force\" Apply requests. It means user will re-acquire conflicting fields owned by other people. Force flag must be unset for non-apply patch requests.
instance HasOptionalParam PatchServiceCIDRStatus Force where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest PatchServiceCIDRStatus contentType res accept
-> Force
-> KubernetesRequest PatchServiceCIDRStatus contentType res accept
applyOptionalParam KubernetesRequest PatchServiceCIDRStatus contentType res accept
req (Force Bool
xs) =
    KubernetesRequest PatchServiceCIDRStatus contentType res accept
req KubernetesRequest PatchServiceCIDRStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest PatchServiceCIDRStatus 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)

-- | @application/apply-patch+yaml@
instance Consumes PatchServiceCIDRStatus MimeApplyPatchyaml
-- | @application/json-patch+json@
instance Consumes PatchServiceCIDRStatus MimeJsonPatchjson
-- | @application/merge-patch+json@
instance Consumes PatchServiceCIDRStatus MimeMergePatchjson
-- | @application/strategic-merge-patch+json@
instance Consumes PatchServiceCIDRStatus MimeStrategicMergePatchjson
-- | @application/apply-patch+cbor@
instance Consumes PatchServiceCIDRStatus MimeApplyPatchcbor

-- | @application/json@
instance Produces PatchServiceCIDRStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces PatchServiceCIDRStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces PatchServiceCIDRStatus MimeCbor
-- | @application/yaml@
instance Produces PatchServiceCIDRStatus MimeYaml


-- *** readIPAddress

-- | @GET \/apis\/networking.k8s.io\/v1beta1\/ipaddresses\/{name}@
-- 
-- read the specified IPAddress
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readIPAddress
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the IPAddress
  -> KubernetesRequest ReadIPAddress MimeNoContent V1beta1IPAddress accept
readIPAddress :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadIPAddress MimeNoContent V1beta1IPAddress accept
readIPAddress  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadIPAddress MimeNoContent V1beta1IPAddress accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/networking.k8s.io/v1beta1/ipaddresses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadIPAddress MimeNoContent V1beta1IPAddress accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadIPAddress MimeNoContent V1beta1IPAddress 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 ReadIPAddress  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadIPAddress Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadIPAddress contentType res accept
-> Pretty -> KubernetesRequest ReadIPAddress contentType res accept
applyOptionalParam KubernetesRequest ReadIPAddress contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadIPAddress contentType res accept
req KubernetesRequest ReadIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadIPAddress 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)
-- | @application/json@
instance Produces ReadIPAddress MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadIPAddress MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadIPAddress MimeCbor
-- | @application/yaml@
instance Produces ReadIPAddress MimeYaml


-- *** readServiceCIDR

-- | @GET \/apis\/networking.k8s.io\/v1beta1\/servicecidrs\/{name}@
-- 
-- read the specified ServiceCIDR
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readServiceCIDR
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceCIDR
  -> KubernetesRequest ReadServiceCIDR MimeNoContent V1beta1ServiceCIDR accept
readServiceCIDR :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadServiceCIDR MimeNoContent V1beta1ServiceCIDR accept
readServiceCIDR  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadServiceCIDR MimeNoContent V1beta1ServiceCIDR accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/networking.k8s.io/v1beta1/servicecidrs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReadServiceCIDR MimeNoContent V1beta1ServiceCIDR accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadServiceCIDR MimeNoContent V1beta1ServiceCIDR 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 ReadServiceCIDR  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadServiceCIDR Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadServiceCIDR contentType res accept
-> Pretty
-> KubernetesRequest ReadServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ReadServiceCIDR contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadServiceCIDR contentType res accept
req KubernetesRequest ReadServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadServiceCIDR 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)
-- | @application/json@
instance Produces ReadServiceCIDR MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadServiceCIDR MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadServiceCIDR MimeCbor
-- | @application/yaml@
instance Produces ReadServiceCIDR MimeYaml


-- *** readServiceCIDRStatus

-- | @GET \/apis\/networking.k8s.io\/v1beta1\/servicecidrs\/{name}\/status@
-- 
-- read status of the specified ServiceCIDR
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
readServiceCIDRStatus
  :: Accept accept -- ^ request accept ('MimeType')
  -> Name -- ^ "name" -  name of the ServiceCIDR
  -> KubernetesRequest ReadServiceCIDRStatus MimeNoContent V1beta1ServiceCIDR accept
readServiceCIDRStatus :: forall accept.
Accept accept
-> Name
-> KubernetesRequest
     ReadServiceCIDRStatus MimeNoContent V1beta1ServiceCIDR accept
readServiceCIDRStatus  Accept accept
_ (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReadServiceCIDRStatus MimeNoContent V1beta1ServiceCIDR accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/apis/networking.k8s.io/v1beta1/servicecidrs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReadServiceCIDRStatus MimeNoContent V1beta1ServiceCIDR accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReadServiceCIDRStatus MimeNoContent V1beta1ServiceCIDR 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 ReadServiceCIDRStatus  

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReadServiceCIDRStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReadServiceCIDRStatus contentType res accept
-> Pretty
-> KubernetesRequest ReadServiceCIDRStatus contentType res accept
applyOptionalParam KubernetesRequest ReadServiceCIDRStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReadServiceCIDRStatus contentType res accept
req KubernetesRequest ReadServiceCIDRStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest ReadServiceCIDRStatus 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)
-- | @application/json@
instance Produces ReadServiceCIDRStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReadServiceCIDRStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReadServiceCIDRStatus MimeCbor
-- | @application/yaml@
instance Produces ReadServiceCIDRStatus MimeYaml


-- *** replaceIPAddress

-- | @PUT \/apis\/networking.k8s.io\/v1beta1\/ipaddresses\/{name}@
-- 
-- replace the specified IPAddress
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceIPAddress
  :: (Consumes ReplaceIPAddress contentType, MimeRender contentType V1beta1IPAddress)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1beta1IPAddress -- ^ "body"
  -> Name -- ^ "name" -  name of the IPAddress
  -> KubernetesRequest ReplaceIPAddress contentType V1beta1IPAddress accept
replaceIPAddress :: forall contentType accept.
(Consumes ReplaceIPAddress contentType,
 MimeRender contentType V1beta1IPAddress) =>
ContentType contentType
-> Accept accept
-> V1beta1IPAddress
-> Name
-> KubernetesRequest
     ReplaceIPAddress contentType V1beta1IPAddress accept
replaceIPAddress ContentType contentType
_  Accept accept
_ V1beta1IPAddress
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceIPAddress contentType V1beta1IPAddress accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/networking.k8s.io/v1beta1/ipaddresses/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceIPAddress contentType V1beta1IPAddress accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceIPAddress contentType V1beta1IPAddress 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
  ReplaceIPAddress contentType V1beta1IPAddress accept
-> V1beta1IPAddress
-> KubernetesRequest
     ReplaceIPAddress contentType V1beta1IPAddress 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
forall contentType res accept.
(Consumes ReplaceIPAddress contentType,
 MimeRender contentType V1beta1IPAddress) =>
KubernetesRequest ReplaceIPAddress contentType res accept
-> V1beta1IPAddress
-> KubernetesRequest ReplaceIPAddress contentType res accept
`setBodyParam` V1beta1IPAddress
body

data ReplaceIPAddress 
instance HasBodyParam ReplaceIPAddress V1beta1IPAddress 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceIPAddress Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceIPAddress contentType res accept
-> Pretty
-> KubernetesRequest ReplaceIPAddress contentType res accept
applyOptionalParam KubernetesRequest ReplaceIPAddress contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceIPAddress contentType res accept
req KubernetesRequest ReplaceIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceIPAddress 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)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceIPAddress DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceIPAddress contentType res accept
-> DryRun
-> KubernetesRequest ReplaceIPAddress contentType res accept
applyOptionalParam KubernetesRequest ReplaceIPAddress contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceIPAddress contentType res accept
req KubernetesRequest ReplaceIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceIPAddress 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)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceIPAddress FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceIPAddress contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceIPAddress contentType res accept
applyOptionalParam KubernetesRequest ReplaceIPAddress contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceIPAddress contentType res accept
req KubernetesRequest ReplaceIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceIPAddress 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)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceIPAddress FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceIPAddress contentType res accept
-> FieldValidation
-> KubernetesRequest ReplaceIPAddress contentType res accept
applyOptionalParam KubernetesRequest ReplaceIPAddress contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceIPAddress contentType res accept
req KubernetesRequest ReplaceIPAddress contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceIPAddress 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
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceIPAddress mtype

-- | @application/json@
instance Produces ReplaceIPAddress MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceIPAddress MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceIPAddress MimeCbor
-- | @application/yaml@
instance Produces ReplaceIPAddress MimeYaml


-- *** replaceServiceCIDR

-- | @PUT \/apis\/networking.k8s.io\/v1beta1\/servicecidrs\/{name}@
-- 
-- replace the specified ServiceCIDR
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceServiceCIDR
  :: (Consumes ReplaceServiceCIDR contentType, MimeRender contentType V1beta1ServiceCIDR)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1beta1ServiceCIDR -- ^ "body"
  -> Name -- ^ "name" -  name of the ServiceCIDR
  -> KubernetesRequest ReplaceServiceCIDR contentType V1beta1ServiceCIDR accept
replaceServiceCIDR :: forall contentType accept.
(Consumes ReplaceServiceCIDR contentType,
 MimeRender contentType V1beta1ServiceCIDR) =>
ContentType contentType
-> Accept accept
-> V1beta1ServiceCIDR
-> Name
-> KubernetesRequest
     ReplaceServiceCIDR contentType V1beta1ServiceCIDR accept
replaceServiceCIDR ContentType contentType
_  Accept accept
_ V1beta1ServiceCIDR
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceServiceCIDR contentType V1beta1ServiceCIDR accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/networking.k8s.io/v1beta1/servicecidrs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name]
    KubernetesRequest
  ReplaceServiceCIDR contentType V1beta1ServiceCIDR accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceServiceCIDR contentType V1beta1ServiceCIDR 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
  ReplaceServiceCIDR contentType V1beta1ServiceCIDR accept
-> V1beta1ServiceCIDR
-> KubernetesRequest
     ReplaceServiceCIDR contentType V1beta1ServiceCIDR 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
forall contentType res accept.
(Consumes ReplaceServiceCIDR contentType,
 MimeRender contentType V1beta1ServiceCIDR) =>
KubernetesRequest ReplaceServiceCIDR contentType res accept
-> V1beta1ServiceCIDR
-> KubernetesRequest ReplaceServiceCIDR contentType res accept
`setBodyParam` V1beta1ServiceCIDR
body

data ReplaceServiceCIDR 
instance HasBodyParam ReplaceServiceCIDR V1beta1ServiceCIDR 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceServiceCIDR Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceServiceCIDR contentType res accept
-> Pretty
-> KubernetesRequest ReplaceServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ReplaceServiceCIDR contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceServiceCIDR contentType res accept
req KubernetesRequest ReplaceServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceServiceCIDR 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)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceServiceCIDR DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceServiceCIDR contentType res accept
-> DryRun
-> KubernetesRequest ReplaceServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ReplaceServiceCIDR contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceServiceCIDR contentType res accept
req KubernetesRequest ReplaceServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceServiceCIDR 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)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceServiceCIDR FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceServiceCIDR contentType res accept
-> FieldManager
-> KubernetesRequest ReplaceServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ReplaceServiceCIDR contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceServiceCIDR contentType res accept
req KubernetesRequest ReplaceServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceServiceCIDR 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)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceServiceCIDR FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceServiceCIDR contentType res accept
-> FieldValidation
-> KubernetesRequest ReplaceServiceCIDR contentType res accept
applyOptionalParam KubernetesRequest ReplaceServiceCIDR contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceServiceCIDR contentType res accept
req KubernetesRequest ReplaceServiceCIDR contentType res accept
-> [QueryItem]
-> KubernetesRequest ReplaceServiceCIDR 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
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceServiceCIDR mtype

-- | @application/json@
instance Produces ReplaceServiceCIDR MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceServiceCIDR MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceServiceCIDR MimeCbor
-- | @application/yaml@
instance Produces ReplaceServiceCIDR MimeYaml


-- *** replaceServiceCIDRStatus

-- | @PUT \/apis\/networking.k8s.io\/v1beta1\/servicecidrs\/{name}\/status@
-- 
-- replace status of the specified ServiceCIDR
-- 
-- AuthMethod: 'AuthApiKeyBearerToken'
-- 
replaceServiceCIDRStatus
  :: (Consumes ReplaceServiceCIDRStatus contentType, MimeRender contentType V1beta1ServiceCIDR)
  => ContentType contentType -- ^ request content-type ('MimeType')
  -> Accept accept -- ^ request accept ('MimeType')
  -> V1beta1ServiceCIDR -- ^ "body"
  -> Name -- ^ "name" -  name of the ServiceCIDR
  -> KubernetesRequest ReplaceServiceCIDRStatus contentType V1beta1ServiceCIDR accept
replaceServiceCIDRStatus :: forall contentType accept.
(Consumes ReplaceServiceCIDRStatus contentType,
 MimeRender contentType V1beta1ServiceCIDR) =>
ContentType contentType
-> Accept accept
-> V1beta1ServiceCIDR
-> Name
-> KubernetesRequest
     ReplaceServiceCIDRStatus contentType V1beta1ServiceCIDR accept
replaceServiceCIDRStatus ContentType contentType
_  Accept accept
_ V1beta1ServiceCIDR
body (Name Text
name) =
  Method
-> [ByteString]
-> KubernetesRequest
     ReplaceServiceCIDRStatus contentType V1beta1ServiceCIDR accept
forall req contentType res accept.
Method
-> [ByteString] -> KubernetesRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/apis/networking.k8s.io/v1beta1/servicecidrs/",Text -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toPath Text
name,ByteString
"/status"]
    KubernetesRequest
  ReplaceServiceCIDRStatus contentType V1beta1ServiceCIDR accept
-> Proxy AuthApiKeyBearerToken
-> KubernetesRequest
     ReplaceServiceCIDRStatus contentType V1beta1ServiceCIDR 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
  ReplaceServiceCIDRStatus contentType V1beta1ServiceCIDR accept
-> V1beta1ServiceCIDR
-> KubernetesRequest
     ReplaceServiceCIDRStatus contentType V1beta1ServiceCIDR 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
forall contentType res accept.
(Consumes ReplaceServiceCIDRStatus contentType,
 MimeRender contentType V1beta1ServiceCIDR) =>
KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
-> V1beta1ServiceCIDR
-> KubernetesRequest
     ReplaceServiceCIDRStatus contentType res accept
`setBodyParam` V1beta1ServiceCIDR
body

data ReplaceServiceCIDRStatus 
instance HasBodyParam ReplaceServiceCIDRStatus V1beta1ServiceCIDR 

-- | /Optional Param/ "pretty" - If 'true', then the output is pretty printed. Defaults to 'false' unless the user-agent indicates a browser or command-line HTTP tool (curl and wget).
instance HasOptionalParam ReplaceServiceCIDRStatus Pretty where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
-> Pretty
-> KubernetesRequest
     ReplaceServiceCIDRStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
req (Pretty Text
xs) =
    KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
req KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceServiceCIDRStatus 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)

-- | /Optional Param/ "dryRun" - When present, indicates that modifications should not be persisted. An invalid or unrecognized dryRun directive will result in an error response and no further processing of the request. Valid values are: - All: all dry run stages will be processed
instance HasOptionalParam ReplaceServiceCIDRStatus DryRun where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
-> DryRun
-> KubernetesRequest
     ReplaceServiceCIDRStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
req (DryRun Text
xs) =
    KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
req KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceServiceCIDRStatus 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)

-- | /Optional Param/ "fieldManager" - fieldManager is a name associated with the actor or entity that is making these changes. The value must be less than or 128 characters long, and only contain printable characters, as defined by https://golang.org/pkg/unicode/#IsPrint.
instance HasOptionalParam ReplaceServiceCIDRStatus FieldManager where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
-> FieldManager
-> KubernetesRequest
     ReplaceServiceCIDRStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
req (FieldManager Text
xs) =
    KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
req KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceServiceCIDRStatus 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)

-- | /Optional Param/ "fieldValidation" - fieldValidation instructs the server on how to handle objects in the request (POST/PUT/PATCH) containing unknown or duplicate fields. Valid values are: - Ignore: This will ignore any unknown fields that are silently dropped from the object, and will ignore all but the last duplicate field that the decoder encounters. This is the default behavior prior to v1.23. - Warn: This will send a warning via the standard warning response header for each unknown field that is dropped from the object, and for each duplicate field that is encountered. The request will still succeed if there are no other errors, and will only persist the last of any duplicate fields. This is the default in v1.23+ - Strict: This will fail the request with a BadRequest error if any unknown fields would be dropped from the object, or if any duplicate fields are present. The error returned from the server will contain all unknown and duplicate fields encountered.
instance HasOptionalParam ReplaceServiceCIDRStatus FieldValidation where
  applyOptionalParam :: forall contentType res accept.
KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
-> FieldValidation
-> KubernetesRequest
     ReplaceServiceCIDRStatus contentType res accept
applyOptionalParam KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
req (FieldValidation Text
xs) =
    KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
req KubernetesRequest ReplaceServiceCIDRStatus contentType res accept
-> [QueryItem]
-> KubernetesRequest
     ReplaceServiceCIDRStatus 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
"fieldValidation", Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs)

-- | @*/*@
instance MimeType mtype => Consumes ReplaceServiceCIDRStatus mtype

-- | @application/json@
instance Produces ReplaceServiceCIDRStatus MimeJSON
-- | @application/vnd.kubernetes.protobuf@
instance Produces ReplaceServiceCIDRStatus MimeVndKubernetesProtobuf
-- | @application/cbor@
instance Produces ReplaceServiceCIDRStatus MimeCbor
-- | @application/yaml@
instance Produces ReplaceServiceCIDRStatus MimeYaml