Safe Haskell | None |
---|---|
Language | Haskell2010 |
Kubernetes.OpenAPI.Core
Description
Synopsis
- data KubernetesClientConfig = KubernetesClientConfig {}
- newConfig :: IO KubernetesClientConfig
- addAuthMethod :: AuthMethod auth => KubernetesClientConfig -> auth -> KubernetesClientConfig
- withStdoutLogging :: KubernetesClientConfig -> IO KubernetesClientConfig
- withStderrLogging :: KubernetesClientConfig -> IO KubernetesClientConfig
- withNoLogging :: KubernetesClientConfig -> KubernetesClientConfig
- data KubernetesRequest req contentType res accept = KubernetesRequest {
- rMethod :: Method
- rUrlPath :: [ByteString]
- rParams :: Params
- rAuthTypes :: [TypeRep]
- rMethodL :: Lens_' (KubernetesRequest req contentType res accept) Method
- rUrlPathL :: Lens_' (KubernetesRequest req contentType res accept) [ByteString]
- rParamsL :: Lens_' (KubernetesRequest req contentType res accept) Params
- rAuthTypesL :: Lens_' (KubernetesRequest req contentType res accept) [TypeRep]
- class HasBodyParam req param where
- setBodyParam :: forall contentType res accept. (Consumes req contentType, MimeRender contentType param) => KubernetesRequest req contentType res accept -> param -> KubernetesRequest req contentType res accept
- class HasOptionalParam req param where
- applyOptionalParam :: KubernetesRequest req contentType res accept -> param -> KubernetesRequest req contentType res accept
- (-&-) :: KubernetesRequest req contentType res accept -> param -> KubernetesRequest req contentType res accept
- data Params = Params {}
- paramsQueryL :: Lens_' Params Query
- paramsHeadersL :: Lens_' Params RequestHeaders
- paramsBodyL :: Lens_' Params ParamBody
- data ParamBody
- _mkRequest :: Method -> [ByteString] -> KubernetesRequest req contentType res accept
- _mkParams :: Params
- setHeader :: KubernetesRequest req contentType res accept -> [Header] -> KubernetesRequest req contentType res accept
- addHeader :: KubernetesRequest req contentType res accept -> [Header] -> KubernetesRequest req contentType res accept
- removeHeader :: KubernetesRequest req contentType res accept -> [HeaderName] -> KubernetesRequest req contentType res accept
- _setContentTypeHeader :: forall req contentType res accept. MimeType contentType => KubernetesRequest req contentType res accept -> KubernetesRequest req contentType res accept
- _setAcceptHeader :: forall req contentType res accept. MimeType accept => KubernetesRequest req contentType res accept -> KubernetesRequest req contentType res accept
- setQuery :: KubernetesRequest req contentType res accept -> [QueryItem] -> KubernetesRequest req contentType res accept
- addQuery :: KubernetesRequest req contentType res accept -> [QueryItem] -> KubernetesRequest req contentType res accept
- addForm :: KubernetesRequest req contentType res accept -> Form -> KubernetesRequest req contentType res accept
- _addMultiFormPart :: KubernetesRequest req contentType res accept -> Part -> KubernetesRequest req contentType res accept
- _setBodyBS :: KubernetesRequest req contentType res accept -> ByteString -> KubernetesRequest req contentType res accept
- _setBodyLBS :: KubernetesRequest req contentType res accept -> ByteString -> KubernetesRequest req contentType res accept
- _hasAuthType :: AuthMethod authMethod => KubernetesRequest req contentType res accept -> Proxy authMethod -> KubernetesRequest req contentType res accept
- toPath :: ToHttpApiData a => a -> ByteString
- toHeader :: ToHttpApiData a => (HeaderName, a) -> [Header]
- toForm :: ToHttpApiData v => (ByteString, v) -> Form
- toQuery :: ToHttpApiData a => (ByteString, Maybe a) -> [QueryItem]
- data CollectionFormat
- toHeaderColl :: ToHttpApiData a => CollectionFormat -> (HeaderName, [a]) -> [Header]
- toFormColl :: ToHttpApiData v => CollectionFormat -> (ByteString, [v]) -> Form
- toQueryColl :: ToHttpApiData a => CollectionFormat -> (ByteString, Maybe [a]) -> Query
- _toColl :: Traversable f => CollectionFormat -> (f a -> [(b, ByteString)]) -> f [a] -> [(b, ByteString)]
- _toCollA :: (Traversable f, Traversable t, Alternative t) => CollectionFormat -> (f (t a) -> [(b, t ByteString)]) -> f (t [a]) -> [(b, t ByteString)]
- _toCollA' :: (Monoid c, Traversable f, Traversable t, Alternative t) => CollectionFormat -> (f (t a) -> [(b, t c)]) -> (Char -> c) -> f (t [a]) -> [(b, t c)]
- class Typeable a => AuthMethod a where
- applyAuthMethod :: KubernetesClientConfig -> a -> KubernetesRequest req contentType res accept -> IO (KubernetesRequest req contentType res accept)
- data AnyAuthMethod = forall a.AuthMethod a => AnyAuthMethod a
- data AuthMethodException = AuthMethodException String
- _applyAuthMethods :: KubernetesRequest req contentType res accept -> KubernetesClientConfig -> IO (KubernetesRequest req contentType res accept)
- _omitNulls :: [(Text, Value)] -> Value
- _toFormItem :: (ToHttpApiData a, Functor f) => t -> f a -> f (t, [Text])
- _emptyToNothing :: Maybe String -> Maybe String
- _memptyToNothing :: (Monoid a, Eq a) => Maybe a -> Maybe a
- newtype DateTime = DateTime {}
- _readDateTime :: MonadFail m => String -> m DateTime
- _showDateTime :: FormatTime t => t -> String
- _parseISO8601 :: (ParseTime t, MonadFail m, Alternative m) => String -> m t
- newtype Date = Date {}
- _readDate :: MonadFail m => String -> m Date
- _showDate :: FormatTime t => t -> String
- newtype ByteArray = ByteArray {}
- _readByteArray :: MonadFail m => Text -> m ByteArray
- _showByteArray :: ByteArray -> Text
- newtype Binary = Binary {}
- _readBinaryBase64 :: MonadFail m => Text -> m Binary
- _showBinaryBase64 :: Binary -> Text
- type Lens_' s a = Lens_ s s a a
- type Lens_ s t a b = forall (f :: * -> *). Functor f => (a -> f b) -> s -> f t
KubernetesClientConfig
data KubernetesClientConfig Source #
Constructors
KubernetesClientConfig | |
Fields
|
Instances
Show KubernetesClientConfig Source # | display the config |
Defined in Kubernetes.OpenAPI.Core Methods showsPrec :: Int -> KubernetesClientConfig -> ShowS # show :: KubernetesClientConfig -> String # showList :: [KubernetesClientConfig] -> ShowS # |
newConfig :: IO KubernetesClientConfig Source #
constructs a default KubernetesClientConfig
configHost:
http://localhost
configUserAgent:
"kubernetes-client-core/0.1.0.0"
addAuthMethod :: AuthMethod auth => KubernetesClientConfig -> auth -> KubernetesClientConfig Source #
updates config use AuthMethod on matching requests
withStdoutLogging :: KubernetesClientConfig -> IO KubernetesClientConfig Source #
updates the config to use stdout logging
withStderrLogging :: KubernetesClientConfig -> IO KubernetesClientConfig Source #
updates the config to use stderr logging
withNoLogging :: KubernetesClientConfig -> KubernetesClientConfig Source #
updates the config to disable logging
KubernetesRequest
data KubernetesRequest req contentType res accept Source #
Represents a request.
Type Variables:
Constructors
KubernetesRequest | |
Fields
|
Instances
Show (KubernetesRequest req contentType res accept) Source # | |
Defined in Kubernetes.OpenAPI.Core Methods showsPrec :: Int -> KubernetesRequest req contentType res accept -> ShowS # show :: KubernetesRequest req contentType res accept -> String # showList :: [KubernetesRequest req contentType res accept] -> ShowS # |
rUrlPathL :: Lens_' (KubernetesRequest req contentType res accept) [ByteString] Source #
rUrlPath
Lens
rAuthTypesL :: Lens_' (KubernetesRequest req contentType res accept) [TypeRep] Source #
rParams
Lens
HasBodyParam
class HasBodyParam req param where Source #
Designates the body parameter of a request
Minimal complete definition
Nothing
Methods
setBodyParam :: forall contentType res accept. (Consumes req contentType, MimeRender contentType param) => KubernetesRequest req contentType res accept -> param -> KubernetesRequest req contentType res accept Source #
Instances
HasOptionalParam
class HasOptionalParam req param where Source #
Designates the optional parameters of a request
Minimal complete definition
Methods
applyOptionalParam :: KubernetesRequest req contentType res accept -> param -> KubernetesRequest req contentType res accept Source #
Apply an optional parameter to a request
(-&-) :: KubernetesRequest req contentType res accept -> param -> KubernetesRequest req contentType res accept infixl 2 Source #
infix operator / alias for addOptionalParam
Instances
HasOptionalParam ReplaceVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReplaceVolumeAttachment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReplaceVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReplaceStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceStorageClass contentType res accept -> Pretty -> KubernetesRequest ReplaceStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ReplaceStorageClass contentType res accept -> Pretty -> KubernetesRequest ReplaceStorageClass contentType res accept Source # | |
HasOptionalParam ReplaceStorageClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceStorageClass contentType res accept -> FieldManager -> KubernetesRequest ReplaceStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ReplaceStorageClass contentType res accept -> FieldManager -> KubernetesRequest ReplaceStorageClass contentType res accept Source # | |
HasOptionalParam ReplaceStorageClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceStorageClass contentType res accept -> DryRun -> KubernetesRequest ReplaceStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ReplaceStorageClass contentType res accept -> DryRun -> KubernetesRequest ReplaceStorageClass contentType res accept Source # | |
HasOptionalParam ReplaceCSINode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCSINode contentType res accept -> Pretty -> KubernetesRequest ReplaceCSINode contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCSINode contentType res accept -> Pretty -> KubernetesRequest ReplaceCSINode contentType res accept Source # | |
HasOptionalParam ReplaceCSINode FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCSINode contentType res accept -> FieldManager -> KubernetesRequest ReplaceCSINode contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCSINode contentType res accept -> FieldManager -> KubernetesRequest ReplaceCSINode contentType res accept Source # | |
HasOptionalParam ReplaceCSINode DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCSINode contentType res accept -> DryRun -> KubernetesRequest ReplaceCSINode contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCSINode contentType res accept -> DryRun -> KubernetesRequest ReplaceCSINode contentType res accept Source # | |
HasOptionalParam ReplaceCSIDriver Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCSIDriver contentType res accept -> Pretty -> KubernetesRequest ReplaceCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCSIDriver contentType res accept -> Pretty -> KubernetesRequest ReplaceCSIDriver contentType res accept Source # | |
HasOptionalParam ReplaceCSIDriver FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCSIDriver contentType res accept -> FieldManager -> KubernetesRequest ReplaceCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCSIDriver contentType res accept -> FieldManager -> KubernetesRequest ReplaceCSIDriver contentType res accept Source # | |
HasOptionalParam ReplaceCSIDriver DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCSIDriver contentType res accept -> DryRun -> KubernetesRequest ReplaceCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCSIDriver contentType res accept -> DryRun -> KubernetesRequest ReplaceCSIDriver contentType res accept Source # | |
HasOptionalParam ReadVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReadVolumeAttachment Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Export -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Export -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReadVolumeAttachment Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Exact -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Exact -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReadStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadStorageClass contentType res accept -> Pretty -> KubernetesRequest ReadStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ReadStorageClass contentType res accept -> Pretty -> KubernetesRequest ReadStorageClass contentType res accept Source # | |
HasOptionalParam ReadStorageClass Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadStorageClass contentType res accept -> Export -> KubernetesRequest ReadStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ReadStorageClass contentType res accept -> Export -> KubernetesRequest ReadStorageClass contentType res accept Source # | |
HasOptionalParam ReadStorageClass Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadStorageClass contentType res accept -> Exact -> KubernetesRequest ReadStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ReadStorageClass contentType res accept -> Exact -> KubernetesRequest ReadStorageClass contentType res accept Source # | |
HasOptionalParam ReadCSINode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCSINode contentType res accept -> Pretty -> KubernetesRequest ReadCSINode contentType res accept Source # (-&-) :: KubernetesRequest ReadCSINode contentType res accept -> Pretty -> KubernetesRequest ReadCSINode contentType res accept Source # | |
HasOptionalParam ReadCSINode Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCSINode contentType res accept -> Export -> KubernetesRequest ReadCSINode contentType res accept Source # (-&-) :: KubernetesRequest ReadCSINode contentType res accept -> Export -> KubernetesRequest ReadCSINode contentType res accept Source # | |
HasOptionalParam ReadCSINode Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCSINode contentType res accept -> Exact -> KubernetesRequest ReadCSINode contentType res accept Source # (-&-) :: KubernetesRequest ReadCSINode contentType res accept -> Exact -> KubernetesRequest ReadCSINode contentType res accept Source # | |
HasOptionalParam ReadCSIDriver Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCSIDriver contentType res accept -> Pretty -> KubernetesRequest ReadCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ReadCSIDriver contentType res accept -> Pretty -> KubernetesRequest ReadCSIDriver contentType res accept Source # | |
HasOptionalParam ReadCSIDriver Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCSIDriver contentType res accept -> Export -> KubernetesRequest ReadCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ReadCSIDriver contentType res accept -> Export -> KubernetesRequest ReadCSIDriver contentType res accept Source # | |
HasOptionalParam ReadCSIDriver Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCSIDriver contentType res accept -> Exact -> KubernetesRequest ReadCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ReadCSIDriver contentType res accept -> Exact -> KubernetesRequest ReadCSIDriver contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachment Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept -> Force -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachment contentType res accept -> Force -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachment FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # | |
HasOptionalParam PatchStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchStorageClass contentType res accept -> Pretty -> KubernetesRequest PatchStorageClass contentType res accept Source # (-&-) :: KubernetesRequest PatchStorageClass contentType res accept -> Pretty -> KubernetesRequest PatchStorageClass contentType res accept Source # | |
HasOptionalParam PatchStorageClass Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchStorageClass contentType res accept -> Force -> KubernetesRequest PatchStorageClass contentType res accept Source # (-&-) :: KubernetesRequest PatchStorageClass contentType res accept -> Force -> KubernetesRequest PatchStorageClass contentType res accept Source # | |
HasOptionalParam PatchStorageClass FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchStorageClass contentType res accept -> FieldManager -> KubernetesRequest PatchStorageClass contentType res accept Source # (-&-) :: KubernetesRequest PatchStorageClass contentType res accept -> FieldManager -> KubernetesRequest PatchStorageClass contentType res accept Source # | |
HasOptionalParam PatchStorageClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchStorageClass contentType res accept -> DryRun -> KubernetesRequest PatchStorageClass contentType res accept Source # (-&-) :: KubernetesRequest PatchStorageClass contentType res accept -> DryRun -> KubernetesRequest PatchStorageClass contentType res accept Source # | |
HasOptionalParam PatchCSINode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCSINode contentType res accept -> Pretty -> KubernetesRequest PatchCSINode contentType res accept Source # (-&-) :: KubernetesRequest PatchCSINode contentType res accept -> Pretty -> KubernetesRequest PatchCSINode contentType res accept Source # | |
HasOptionalParam PatchCSINode Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCSINode contentType res accept -> Force -> KubernetesRequest PatchCSINode contentType res accept Source # (-&-) :: KubernetesRequest PatchCSINode contentType res accept -> Force -> KubernetesRequest PatchCSINode contentType res accept Source # | |
HasOptionalParam PatchCSINode FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCSINode contentType res accept -> FieldManager -> KubernetesRequest PatchCSINode contentType res accept Source # (-&-) :: KubernetesRequest PatchCSINode contentType res accept -> FieldManager -> KubernetesRequest PatchCSINode contentType res accept Source # | |
HasOptionalParam PatchCSINode DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCSINode contentType res accept -> DryRun -> KubernetesRequest PatchCSINode contentType res accept Source # (-&-) :: KubernetesRequest PatchCSINode contentType res accept -> DryRun -> KubernetesRequest PatchCSINode contentType res accept Source # | |
HasOptionalParam PatchCSIDriver Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCSIDriver contentType res accept -> Pretty -> KubernetesRequest PatchCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest PatchCSIDriver contentType res accept -> Pretty -> KubernetesRequest PatchCSIDriver contentType res accept Source # | |
HasOptionalParam PatchCSIDriver Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCSIDriver contentType res accept -> Force -> KubernetesRequest PatchCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest PatchCSIDriver contentType res accept -> Force -> KubernetesRequest PatchCSIDriver contentType res accept Source # | |
HasOptionalParam PatchCSIDriver FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCSIDriver contentType res accept -> FieldManager -> KubernetesRequest PatchCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest PatchCSIDriver contentType res accept -> FieldManager -> KubernetesRequest PatchCSIDriver contentType res accept Source # | |
HasOptionalParam PatchCSIDriver DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCSIDriver contentType res accept -> DryRun -> KubernetesRequest PatchCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest PatchCSIDriver contentType res accept -> DryRun -> KubernetesRequest PatchCSIDriver contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> Watch -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> Watch -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> ResourceVersion -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> ResourceVersion -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> Limit -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> Limit -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> LabelSelector -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> LabelSelector -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> FieldSelector -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> FieldSelector -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> Continue -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> Continue -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListStorageClass Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> Watch -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> Watch -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> ResourceVersion -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> ResourceVersion -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> Pretty -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> Pretty -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> Limit -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> Limit -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> LabelSelector -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> LabelSelector -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> FieldSelector -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> FieldSelector -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> Continue -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> Continue -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListCSINode Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept -> Watch -> KubernetesRequest ListCSINode contentType res accept Source # (-&-) :: KubernetesRequest ListCSINode contentType res accept -> Watch -> KubernetesRequest ListCSINode contentType res accept Source # | |
HasOptionalParam ListCSINode TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCSINode contentType res accept Source # (-&-) :: KubernetesRequest ListCSINode contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCSINode contentType res accept Source # | |
HasOptionalParam ListCSINode ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept -> ResourceVersion -> KubernetesRequest ListCSINode contentType res accept Source # (-&-) :: KubernetesRequest ListCSINode contentType res accept -> ResourceVersion -> KubernetesRequest ListCSINode contentType res accept Source # | |
HasOptionalParam ListCSINode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept -> Pretty -> KubernetesRequest ListCSINode contentType res accept Source # (-&-) :: KubernetesRequest ListCSINode contentType res accept -> Pretty -> KubernetesRequest ListCSINode contentType res accept Source # | |
HasOptionalParam ListCSINode Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept -> Limit -> KubernetesRequest ListCSINode contentType res accept Source # (-&-) :: KubernetesRequest ListCSINode contentType res accept -> Limit -> KubernetesRequest ListCSINode contentType res accept Source # | |
HasOptionalParam ListCSINode LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept -> LabelSelector -> KubernetesRequest ListCSINode contentType res accept Source # (-&-) :: KubernetesRequest ListCSINode contentType res accept -> LabelSelector -> KubernetesRequest ListCSINode contentType res accept Source # | |
HasOptionalParam ListCSINode FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept -> FieldSelector -> KubernetesRequest ListCSINode contentType res accept Source # (-&-) :: KubernetesRequest ListCSINode contentType res accept -> FieldSelector -> KubernetesRequest ListCSINode contentType res accept Source # | |
HasOptionalParam ListCSINode Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept -> Continue -> KubernetesRequest ListCSINode contentType res accept Source # (-&-) :: KubernetesRequest ListCSINode contentType res accept -> Continue -> KubernetesRequest ListCSINode contentType res accept Source # | |
HasOptionalParam ListCSINode AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSINode contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCSINode contentType res accept Source # (-&-) :: KubernetesRequest ListCSINode contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCSINode contentType res accept Source # | |
HasOptionalParam ListCSIDriver Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept -> Watch -> KubernetesRequest ListCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ListCSIDriver contentType res accept -> Watch -> KubernetesRequest ListCSIDriver contentType res accept Source # | |
HasOptionalParam ListCSIDriver TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ListCSIDriver contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCSIDriver contentType res accept Source # | |
HasOptionalParam ListCSIDriver ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept -> ResourceVersion -> KubernetesRequest ListCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ListCSIDriver contentType res accept -> ResourceVersion -> KubernetesRequest ListCSIDriver contentType res accept Source # | |
HasOptionalParam ListCSIDriver Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept -> Pretty -> KubernetesRequest ListCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ListCSIDriver contentType res accept -> Pretty -> KubernetesRequest ListCSIDriver contentType res accept Source # | |
HasOptionalParam ListCSIDriver Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept -> Limit -> KubernetesRequest ListCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ListCSIDriver contentType res accept -> Limit -> KubernetesRequest ListCSIDriver contentType res accept Source # | |
HasOptionalParam ListCSIDriver LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept -> LabelSelector -> KubernetesRequest ListCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ListCSIDriver contentType res accept -> LabelSelector -> KubernetesRequest ListCSIDriver contentType res accept Source # | |
HasOptionalParam ListCSIDriver FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept -> FieldSelector -> KubernetesRequest ListCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ListCSIDriver contentType res accept -> FieldSelector -> KubernetesRequest ListCSIDriver contentType res accept Source # | |
HasOptionalParam ListCSIDriver Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept -> Continue -> KubernetesRequest ListCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ListCSIDriver contentType res accept -> Continue -> KubernetesRequest ListCSIDriver contentType res accept Source # | |
HasOptionalParam ListCSIDriver AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCSIDriver contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest ListCSIDriver contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteStorageClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteStorageClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteStorageClass contentType res accept Source # | |
HasOptionalParam DeleteStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept -> Pretty -> KubernetesRequest DeleteStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteStorageClass contentType res accept -> Pretty -> KubernetesRequest DeleteStorageClass contentType res accept Source # | |
HasOptionalParam DeleteStorageClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteStorageClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteStorageClass contentType res accept Source # | |
HasOptionalParam DeleteStorageClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteStorageClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteStorageClass contentType res accept Source # | |
HasOptionalParam DeleteStorageClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept -> DryRun -> KubernetesRequest DeleteStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteStorageClass contentType res accept -> DryRun -> KubernetesRequest DeleteStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSINode TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSINode ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSINode PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSINode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSINode OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSINode Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> Limit -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> Limit -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSINode LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSINode GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSINode FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSINode DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSINode Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> Continue -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSINode contentType res accept -> Continue -> KubernetesRequest DeleteCollectionCSINode contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSIDriver TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSIDriver ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSIDriver PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSIDriver Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSIDriver OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSIDriver Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> Limit -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> Limit -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSIDriver LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSIDriver GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSIDriver FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSIDriver DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCollectionCSIDriver Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> Continue -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCSIDriver contentType res accept -> Continue -> KubernetesRequest DeleteCollectionCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCSINode PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCSINode contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCSINode contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCSINode contentType res accept Source # | |
HasOptionalParam DeleteCSINode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCSINode contentType res accept -> Pretty -> KubernetesRequest DeleteCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCSINode contentType res accept -> Pretty -> KubernetesRequest DeleteCSINode contentType res accept Source # | |
HasOptionalParam DeleteCSINode OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCSINode contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCSINode contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCSINode contentType res accept Source # | |
HasOptionalParam DeleteCSINode GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCSINode contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCSINode contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCSINode contentType res accept Source # | |
HasOptionalParam DeleteCSINode DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCSINode contentType res accept -> DryRun -> KubernetesRequest DeleteCSINode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCSINode contentType res accept -> DryRun -> KubernetesRequest DeleteCSINode contentType res accept Source # | |
HasOptionalParam DeleteCSIDriver PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCSIDriver contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCSIDriver contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCSIDriver Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCSIDriver contentType res accept -> Pretty -> KubernetesRequest DeleteCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCSIDriver contentType res accept -> Pretty -> KubernetesRequest DeleteCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCSIDriver OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCSIDriver contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCSIDriver contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCSIDriver GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCSIDriver contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCSIDriver contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCSIDriver contentType res accept Source # | |
HasOptionalParam DeleteCSIDriver DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCSIDriver contentType res accept -> DryRun -> KubernetesRequest DeleteCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest DeleteCSIDriver contentType res accept -> DryRun -> KubernetesRequest DeleteCSIDriver contentType res accept Source # | |
HasOptionalParam CreateVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest CreateVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # | |
HasOptionalParam CreateVolumeAttachment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest CreateVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # | |
HasOptionalParam CreateVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest CreateVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # | |
HasOptionalParam CreateStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateStorageClass contentType res accept -> Pretty -> KubernetesRequest CreateStorageClass contentType res accept Source # (-&-) :: KubernetesRequest CreateStorageClass contentType res accept -> Pretty -> KubernetesRequest CreateStorageClass contentType res accept Source # | |
HasOptionalParam CreateStorageClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateStorageClass contentType res accept -> FieldManager -> KubernetesRequest CreateStorageClass contentType res accept Source # (-&-) :: KubernetesRequest CreateStorageClass contentType res accept -> FieldManager -> KubernetesRequest CreateStorageClass contentType res accept Source # | |
HasOptionalParam CreateStorageClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateStorageClass contentType res accept -> DryRun -> KubernetesRequest CreateStorageClass contentType res accept Source # (-&-) :: KubernetesRequest CreateStorageClass contentType res accept -> DryRun -> KubernetesRequest CreateStorageClass contentType res accept Source # | |
HasOptionalParam CreateCSINode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateCSINode contentType res accept -> Pretty -> KubernetesRequest CreateCSINode contentType res accept Source # (-&-) :: KubernetesRequest CreateCSINode contentType res accept -> Pretty -> KubernetesRequest CreateCSINode contentType res accept Source # | |
HasOptionalParam CreateCSINode FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateCSINode contentType res accept -> FieldManager -> KubernetesRequest CreateCSINode contentType res accept Source # (-&-) :: KubernetesRequest CreateCSINode contentType res accept -> FieldManager -> KubernetesRequest CreateCSINode contentType res accept Source # | |
HasOptionalParam CreateCSINode DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateCSINode contentType res accept -> DryRun -> KubernetesRequest CreateCSINode contentType res accept Source # (-&-) :: KubernetesRequest CreateCSINode contentType res accept -> DryRun -> KubernetesRequest CreateCSINode contentType res accept Source # | |
HasOptionalParam CreateCSIDriver Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateCSIDriver contentType res accept -> Pretty -> KubernetesRequest CreateCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest CreateCSIDriver contentType res accept -> Pretty -> KubernetesRequest CreateCSIDriver contentType res accept Source # | |
HasOptionalParam CreateCSIDriver FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateCSIDriver contentType res accept -> FieldManager -> KubernetesRequest CreateCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest CreateCSIDriver contentType res accept -> FieldManager -> KubernetesRequest CreateCSIDriver contentType res accept Source # | |
HasOptionalParam CreateCSIDriver DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateCSIDriver contentType res accept -> DryRun -> KubernetesRequest CreateCSIDriver contentType res accept Source # (-&-) :: KubernetesRequest CreateCSIDriver contentType res accept -> DryRun -> KubernetesRequest CreateCSIDriver contentType res accept Source # | |
HasOptionalParam ReplaceVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReplaceVolumeAttachment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReplaceVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReadVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReadVolumeAttachment Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Export -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Export -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReadVolumeAttachment Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Exact -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Exact -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachment Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept -> Force -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachment contentType res accept -> Force -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachment FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> Watch -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> Watch -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> ResourceVersion -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> ResourceVersion -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> Limit -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> Limit -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> LabelSelector -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> LabelSelector -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> FieldSelector -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> FieldSelector -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> Continue -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> Continue -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam CreateVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest CreateVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # | |
HasOptionalParam CreateVolumeAttachment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest CreateVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # | |
HasOptionalParam CreateVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest CreateVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReplaceVolumeAttachmentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachmentStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceVolumeAttachmentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceVolumeAttachmentStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceVolumeAttachmentStatus contentType res accept Source # | |
HasOptionalParam ReplaceVolumeAttachmentStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachmentStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceVolumeAttachmentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceVolumeAttachmentStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceVolumeAttachmentStatus contentType res accept Source # | |
HasOptionalParam ReplaceVolumeAttachmentStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachmentStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceVolumeAttachmentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceVolumeAttachmentStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceVolumeAttachmentStatus contentType res accept Source # | |
HasOptionalParam ReplaceVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReplaceVolumeAttachment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReplaceVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest ReplaceVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReplaceStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReplaceStorageClass contentType res accept -> Pretty -> KubernetesRequest ReplaceStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ReplaceStorageClass contentType res accept -> Pretty -> KubernetesRequest ReplaceStorageClass contentType res accept Source # | |
HasOptionalParam ReplaceStorageClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReplaceStorageClass contentType res accept -> FieldManager -> KubernetesRequest ReplaceStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ReplaceStorageClass contentType res accept -> FieldManager -> KubernetesRequest ReplaceStorageClass contentType res accept Source # | |
HasOptionalParam ReplaceStorageClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReplaceStorageClass contentType res accept -> DryRun -> KubernetesRequest ReplaceStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ReplaceStorageClass contentType res accept -> DryRun -> KubernetesRequest ReplaceStorageClass contentType res accept Source # | |
HasOptionalParam ReadVolumeAttachmentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReadVolumeAttachmentStatus contentType res accept -> Pretty -> KubernetesRequest ReadVolumeAttachmentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadVolumeAttachmentStatus contentType res accept -> Pretty -> KubernetesRequest ReadVolumeAttachmentStatus contentType res accept Source # | |
HasOptionalParam ReadVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReadVolumeAttachment Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Export -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Export -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReadVolumeAttachment Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Exact -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ReadVolumeAttachment contentType res accept -> Exact -> KubernetesRequest ReadVolumeAttachment contentType res accept Source # | |
HasOptionalParam ReadStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReadStorageClass contentType res accept -> Pretty -> KubernetesRequest ReadStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ReadStorageClass contentType res accept -> Pretty -> KubernetesRequest ReadStorageClass contentType res accept Source # | |
HasOptionalParam ReadStorageClass Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReadStorageClass contentType res accept -> Export -> KubernetesRequest ReadStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ReadStorageClass contentType res accept -> Export -> KubernetesRequest ReadStorageClass contentType res accept Source # | |
HasOptionalParam ReadStorageClass Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ReadStorageClass contentType res accept -> Exact -> KubernetesRequest ReadStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ReadStorageClass contentType res accept -> Exact -> KubernetesRequest ReadStorageClass contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachmentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachmentStatus contentType res accept -> Pretty -> KubernetesRequest PatchVolumeAttachmentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachmentStatus contentType res accept -> Pretty -> KubernetesRequest PatchVolumeAttachmentStatus contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachmentStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachmentStatus contentType res accept -> Force -> KubernetesRequest PatchVolumeAttachmentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachmentStatus contentType res accept -> Force -> KubernetesRequest PatchVolumeAttachmentStatus contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachmentStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachmentStatus contentType res accept -> FieldManager -> KubernetesRequest PatchVolumeAttachmentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachmentStatus contentType res accept -> FieldManager -> KubernetesRequest PatchVolumeAttachmentStatus contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachmentStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachmentStatus contentType res accept -> DryRun -> KubernetesRequest PatchVolumeAttachmentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachmentStatus contentType res accept -> DryRun -> KubernetesRequest PatchVolumeAttachmentStatus contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachment Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept -> Force -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachment contentType res accept -> Force -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachment FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # | |
HasOptionalParam PatchVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest PatchVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest PatchVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest PatchVolumeAttachment contentType res accept Source # | |
HasOptionalParam PatchStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest PatchStorageClass contentType res accept -> Pretty -> KubernetesRequest PatchStorageClass contentType res accept Source # (-&-) :: KubernetesRequest PatchStorageClass contentType res accept -> Pretty -> KubernetesRequest PatchStorageClass contentType res accept Source # | |
HasOptionalParam PatchStorageClass Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest PatchStorageClass contentType res accept -> Force -> KubernetesRequest PatchStorageClass contentType res accept Source # (-&-) :: KubernetesRequest PatchStorageClass contentType res accept -> Force -> KubernetesRequest PatchStorageClass contentType res accept Source # | |
HasOptionalParam PatchStorageClass FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest PatchStorageClass contentType res accept -> FieldManager -> KubernetesRequest PatchStorageClass contentType res accept Source # (-&-) :: KubernetesRequest PatchStorageClass contentType res accept -> FieldManager -> KubernetesRequest PatchStorageClass contentType res accept Source # | |
HasOptionalParam PatchStorageClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest PatchStorageClass contentType res accept -> DryRun -> KubernetesRequest PatchStorageClass contentType res accept Source # (-&-) :: KubernetesRequest PatchStorageClass contentType res accept -> DryRun -> KubernetesRequest PatchStorageClass contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> Watch -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> Watch -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> ResourceVersion -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> ResourceVersion -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> Limit -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> Limit -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> LabelSelector -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> LabelSelector -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> FieldSelector -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> FieldSelector -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> Continue -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> Continue -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListVolumeAttachment AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListVolumeAttachment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest ListVolumeAttachment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListVolumeAttachment contentType res accept Source # | |
HasOptionalParam ListStorageClass Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> Watch -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> Watch -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> ResourceVersion -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> ResourceVersion -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> Pretty -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> Pretty -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> Limit -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> Limit -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> LabelSelector -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> LabelSelector -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> FieldSelector -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> FieldSelector -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> Continue -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> Continue -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam ListStorageClass AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest ListStorageClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListStorageClass contentType res accept Source # (-&-) :: KubernetesRequest ListStorageClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListStorageClass contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest DeleteVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteStorageClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteStorageClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteStorageClass contentType res accept Source # | |
HasOptionalParam DeleteStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept -> Pretty -> KubernetesRequest DeleteStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteStorageClass contentType res accept -> Pretty -> KubernetesRequest DeleteStorageClass contentType res accept Source # | |
HasOptionalParam DeleteStorageClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteStorageClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteStorageClass contentType res accept Source # | |
HasOptionalParam DeleteStorageClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteStorageClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteStorageClass contentType res accept Source # | |
HasOptionalParam DeleteStorageClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteStorageClass contentType res accept -> DryRun -> KubernetesRequest DeleteStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteStorageClass contentType res accept -> DryRun -> KubernetesRequest DeleteStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionVolumeAttachment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionVolumeAttachment contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionStorageClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionStorageClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionStorageClass contentType res accept Source # | |
HasOptionalParam CreateVolumeAttachment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest CreateVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest CreateVolumeAttachment contentType res accept -> Pretty -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # | |
HasOptionalParam CreateVolumeAttachment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest CreateVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest CreateVolumeAttachment contentType res accept -> FieldManager -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # | |
HasOptionalParam CreateVolumeAttachment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest CreateVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # (-&-) :: KubernetesRequest CreateVolumeAttachment contentType res accept -> DryRun -> KubernetesRequest CreateVolumeAttachment contentType res accept Source # | |
HasOptionalParam CreateStorageClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest CreateStorageClass contentType res accept -> Pretty -> KubernetesRequest CreateStorageClass contentType res accept Source # (-&-) :: KubernetesRequest CreateStorageClass contentType res accept -> Pretty -> KubernetesRequest CreateStorageClass contentType res accept Source # | |
HasOptionalParam CreateStorageClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest CreateStorageClass contentType res accept -> FieldManager -> KubernetesRequest CreateStorageClass contentType res accept Source # (-&-) :: KubernetesRequest CreateStorageClass contentType res accept -> FieldManager -> KubernetesRequest CreateStorageClass contentType res accept Source # | |
HasOptionalParam CreateStorageClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.StorageV1 Methods applyOptionalParam :: KubernetesRequest CreateStorageClass contentType res accept -> DryRun -> KubernetesRequest CreateStorageClass contentType res accept Source # (-&-) :: KubernetesRequest CreateStorageClass contentType res accept -> DryRun -> KubernetesRequest CreateStorageClass contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodPreset Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodPreset FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodPreset contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodPreset contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodPreset DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodPreset contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodPreset contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodPreset Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodPreset Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodPreset contentType res accept -> Export -> KubernetesRequest ReadNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodPreset contentType res accept -> Export -> KubernetesRequest ReadNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodPreset Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodPreset contentType res accept -> Exact -> KubernetesRequest ReadNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodPreset contentType res accept -> Exact -> KubernetesRequest ReadNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodPreset Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodPreset Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodPreset contentType res accept -> Force -> KubernetesRequest PatchNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodPreset contentType res accept -> Force -> KubernetesRequest PatchNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodPreset FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodPreset contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodPreset contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodPreset DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodPreset contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodPreset contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ListPodPresetForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodPresetForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodPresetForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodPresetForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodPresetForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodPresetForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodPresetForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodPresetForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodPresetForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodPresetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPodPresetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNamespacedPodPreset Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> Watch -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> Watch -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ListNamespacedPodPreset TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ListNamespacedPodPreset ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ListNamespacedPodPreset Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ListNamespacedPodPreset Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> Limit -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> Limit -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ListNamespacedPodPreset LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ListNamespacedPodPreset FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ListNamespacedPodPreset Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> Continue -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> Continue -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ListNamespacedPodPreset AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodPreset contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodPreset PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodPreset contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodPreset contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodPreset Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodPreset OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodPreset contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodPreset contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodPreset GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodPreset contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodPreset contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodPreset DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodPreset contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodPreset contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodPreset TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodPreset ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodPreset PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodPreset Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodPreset OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodPreset Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodPreset LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodPreset GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodPreset FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodPreset DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodPreset Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodPreset Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodPreset contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodPreset FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodPreset contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodPreset contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodPreset DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SettingsV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodPreset contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPodPreset contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodPreset contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPodPreset contentType res accept Source # | |
HasOptionalParam ReplacePriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplacePriorityClass contentType res accept -> Pretty -> KubernetesRequest ReplacePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReplacePriorityClass contentType res accept -> Pretty -> KubernetesRequest ReplacePriorityClass contentType res accept Source # | |
HasOptionalParam ReplacePriorityClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplacePriorityClass contentType res accept -> FieldManager -> KubernetesRequest ReplacePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReplacePriorityClass contentType res accept -> FieldManager -> KubernetesRequest ReplacePriorityClass contentType res accept Source # | |
HasOptionalParam ReplacePriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplacePriorityClass contentType res accept -> DryRun -> KubernetesRequest ReplacePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReplacePriorityClass contentType res accept -> DryRun -> KubernetesRequest ReplacePriorityClass contentType res accept Source # | |
HasOptionalParam ReadPriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadPriorityClass contentType res accept -> Pretty -> KubernetesRequest ReadPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReadPriorityClass contentType res accept -> Pretty -> KubernetesRequest ReadPriorityClass contentType res accept Source # | |
HasOptionalParam ReadPriorityClass Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadPriorityClass contentType res accept -> Export -> KubernetesRequest ReadPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReadPriorityClass contentType res accept -> Export -> KubernetesRequest ReadPriorityClass contentType res accept Source # | |
HasOptionalParam ReadPriorityClass Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadPriorityClass contentType res accept -> Exact -> KubernetesRequest ReadPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReadPriorityClass contentType res accept -> Exact -> KubernetesRequest ReadPriorityClass contentType res accept Source # | |
HasOptionalParam PatchPriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchPriorityClass contentType res accept -> Pretty -> KubernetesRequest PatchPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest PatchPriorityClass contentType res accept -> Pretty -> KubernetesRequest PatchPriorityClass contentType res accept Source # | |
HasOptionalParam PatchPriorityClass Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchPriorityClass contentType res accept -> Force -> KubernetesRequest PatchPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest PatchPriorityClass contentType res accept -> Force -> KubernetesRequest PatchPriorityClass contentType res accept Source # | |
HasOptionalParam PatchPriorityClass FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchPriorityClass contentType res accept -> FieldManager -> KubernetesRequest PatchPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest PatchPriorityClass contentType res accept -> FieldManager -> KubernetesRequest PatchPriorityClass contentType res accept Source # | |
HasOptionalParam PatchPriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchPriorityClass contentType res accept -> DryRun -> KubernetesRequest PatchPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest PatchPriorityClass contentType res accept -> DryRun -> KubernetesRequest PatchPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> Watch -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> Watch -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> ResourceVersion -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> ResourceVersion -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> Pretty -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> Pretty -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> Limit -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> Limit -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> LabelSelector -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> LabelSelector -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> FieldSelector -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> FieldSelector -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> Continue -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> Continue -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> Pretty -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> Pretty -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> OrphanDependents -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> OrphanDependents -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> DryRun -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> DryRun -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam CreatePriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest CreatePriorityClass contentType res accept -> Pretty -> KubernetesRequest CreatePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest CreatePriorityClass contentType res accept -> Pretty -> KubernetesRequest CreatePriorityClass contentType res accept Source # | |
HasOptionalParam CreatePriorityClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest CreatePriorityClass contentType res accept -> FieldManager -> KubernetesRequest CreatePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest CreatePriorityClass contentType res accept -> FieldManager -> KubernetesRequest CreatePriorityClass contentType res accept Source # | |
HasOptionalParam CreatePriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1beta1 Methods applyOptionalParam :: KubernetesRequest CreatePriorityClass contentType res accept -> DryRun -> KubernetesRequest CreatePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest CreatePriorityClass contentType res accept -> DryRun -> KubernetesRequest CreatePriorityClass contentType res accept Source # | |
HasOptionalParam ReplacePriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplacePriorityClass contentType res accept -> Pretty -> KubernetesRequest ReplacePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReplacePriorityClass contentType res accept -> Pretty -> KubernetesRequest ReplacePriorityClass contentType res accept Source # | |
HasOptionalParam ReplacePriorityClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplacePriorityClass contentType res accept -> FieldManager -> KubernetesRequest ReplacePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReplacePriorityClass contentType res accept -> FieldManager -> KubernetesRequest ReplacePriorityClass contentType res accept Source # | |
HasOptionalParam ReplacePriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplacePriorityClass contentType res accept -> DryRun -> KubernetesRequest ReplacePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReplacePriorityClass contentType res accept -> DryRun -> KubernetesRequest ReplacePriorityClass contentType res accept Source # | |
HasOptionalParam ReadPriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadPriorityClass contentType res accept -> Pretty -> KubernetesRequest ReadPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReadPriorityClass contentType res accept -> Pretty -> KubernetesRequest ReadPriorityClass contentType res accept Source # | |
HasOptionalParam ReadPriorityClass Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadPriorityClass contentType res accept -> Export -> KubernetesRequest ReadPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReadPriorityClass contentType res accept -> Export -> KubernetesRequest ReadPriorityClass contentType res accept Source # | |
HasOptionalParam ReadPriorityClass Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadPriorityClass contentType res accept -> Exact -> KubernetesRequest ReadPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReadPriorityClass contentType res accept -> Exact -> KubernetesRequest ReadPriorityClass contentType res accept Source # | |
HasOptionalParam PatchPriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchPriorityClass contentType res accept -> Pretty -> KubernetesRequest PatchPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest PatchPriorityClass contentType res accept -> Pretty -> KubernetesRequest PatchPriorityClass contentType res accept Source # | |
HasOptionalParam PatchPriorityClass Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchPriorityClass contentType res accept -> Force -> KubernetesRequest PatchPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest PatchPriorityClass contentType res accept -> Force -> KubernetesRequest PatchPriorityClass contentType res accept Source # | |
HasOptionalParam PatchPriorityClass FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchPriorityClass contentType res accept -> FieldManager -> KubernetesRequest PatchPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest PatchPriorityClass contentType res accept -> FieldManager -> KubernetesRequest PatchPriorityClass contentType res accept Source # | |
HasOptionalParam PatchPriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchPriorityClass contentType res accept -> DryRun -> KubernetesRequest PatchPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest PatchPriorityClass contentType res accept -> DryRun -> KubernetesRequest PatchPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> Watch -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> Watch -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> ResourceVersion -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> ResourceVersion -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> Pretty -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> Pretty -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> Limit -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> Limit -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> LabelSelector -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> LabelSelector -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> FieldSelector -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> FieldSelector -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> Continue -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> Continue -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> Pretty -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> Pretty -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> OrphanDependents -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> OrphanDependents -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> DryRun -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> DryRun -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam CreatePriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreatePriorityClass contentType res accept -> Pretty -> KubernetesRequest CreatePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest CreatePriorityClass contentType res accept -> Pretty -> KubernetesRequest CreatePriorityClass contentType res accept Source # | |
HasOptionalParam CreatePriorityClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreatePriorityClass contentType res accept -> FieldManager -> KubernetesRequest CreatePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest CreatePriorityClass contentType res accept -> FieldManager -> KubernetesRequest CreatePriorityClass contentType res accept Source # | |
HasOptionalParam CreatePriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreatePriorityClass contentType res accept -> DryRun -> KubernetesRequest CreatePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest CreatePriorityClass contentType res accept -> DryRun -> KubernetesRequest CreatePriorityClass contentType res accept Source # | |
HasOptionalParam ReplacePriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ReplacePriorityClass contentType res accept -> Pretty -> KubernetesRequest ReplacePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReplacePriorityClass contentType res accept -> Pretty -> KubernetesRequest ReplacePriorityClass contentType res accept Source # | |
HasOptionalParam ReplacePriorityClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ReplacePriorityClass contentType res accept -> FieldManager -> KubernetesRequest ReplacePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReplacePriorityClass contentType res accept -> FieldManager -> KubernetesRequest ReplacePriorityClass contentType res accept Source # | |
HasOptionalParam ReplacePriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ReplacePriorityClass contentType res accept -> DryRun -> KubernetesRequest ReplacePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReplacePriorityClass contentType res accept -> DryRun -> KubernetesRequest ReplacePriorityClass contentType res accept Source # | |
HasOptionalParam ReadPriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ReadPriorityClass contentType res accept -> Pretty -> KubernetesRequest ReadPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReadPriorityClass contentType res accept -> Pretty -> KubernetesRequest ReadPriorityClass contentType res accept Source # | |
HasOptionalParam ReadPriorityClass Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ReadPriorityClass contentType res accept -> Export -> KubernetesRequest ReadPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReadPriorityClass contentType res accept -> Export -> KubernetesRequest ReadPriorityClass contentType res accept Source # | |
HasOptionalParam ReadPriorityClass Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ReadPriorityClass contentType res accept -> Exact -> KubernetesRequest ReadPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ReadPriorityClass contentType res accept -> Exact -> KubernetesRequest ReadPriorityClass contentType res accept Source # | |
HasOptionalParam PatchPriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest PatchPriorityClass contentType res accept -> Pretty -> KubernetesRequest PatchPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest PatchPriorityClass contentType res accept -> Pretty -> KubernetesRequest PatchPriorityClass contentType res accept Source # | |
HasOptionalParam PatchPriorityClass Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest PatchPriorityClass contentType res accept -> Force -> KubernetesRequest PatchPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest PatchPriorityClass contentType res accept -> Force -> KubernetesRequest PatchPriorityClass contentType res accept Source # | |
HasOptionalParam PatchPriorityClass FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest PatchPriorityClass contentType res accept -> FieldManager -> KubernetesRequest PatchPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest PatchPriorityClass contentType res accept -> FieldManager -> KubernetesRequest PatchPriorityClass contentType res accept Source # | |
HasOptionalParam PatchPriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest PatchPriorityClass contentType res accept -> DryRun -> KubernetesRequest PatchPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest PatchPriorityClass contentType res accept -> DryRun -> KubernetesRequest PatchPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> Watch -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> Watch -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> ResourceVersion -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> ResourceVersion -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> Pretty -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> Pretty -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> Limit -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> Limit -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> LabelSelector -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> LabelSelector -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> FieldSelector -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> FieldSelector -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> Continue -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> Continue -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam ListPriorityClass AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest ListPriorityClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest ListPriorityClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> Pretty -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> Pretty -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> OrphanDependents -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> OrphanDependents -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeletePriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeletePriorityClass contentType res accept -> DryRun -> KubernetesRequest DeletePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeletePriorityClass contentType res accept -> DryRun -> KubernetesRequest DeletePriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionPriorityClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPriorityClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionPriorityClass contentType res accept Source # | |
HasOptionalParam CreatePriorityClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest CreatePriorityClass contentType res accept -> Pretty -> KubernetesRequest CreatePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest CreatePriorityClass contentType res accept -> Pretty -> KubernetesRequest CreatePriorityClass contentType res accept Source # | |
HasOptionalParam CreatePriorityClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest CreatePriorityClass contentType res accept -> FieldManager -> KubernetesRequest CreatePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest CreatePriorityClass contentType res accept -> FieldManager -> KubernetesRequest CreatePriorityClass contentType res accept Source # | |
HasOptionalParam CreatePriorityClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.SchedulingV1 Methods applyOptionalParam :: KubernetesRequest CreatePriorityClass contentType res accept -> DryRun -> KubernetesRequest CreatePriorityClass contentType res accept Source # (-&-) :: KubernetesRequest CreatePriorityClass contentType res accept -> DryRun -> KubernetesRequest CreatePriorityClass contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRoleBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRole FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # | |
HasOptionalParam ReplaceClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceClusterRoleBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRole contentType res accept -> Pretty -> KubernetesRequest ReplaceClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRole contentType res accept -> Pretty -> KubernetesRequest ReplaceClusterRole contentType res accept Source # | |
HasOptionalParam ReplaceClusterRole FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRole contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRole contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterRole contentType res accept Source # | |
HasOptionalParam ReplaceClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRole contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRole contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterRole contentType res accept Source # | |
HasOptionalParam ReadNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ReadNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedRole contentType res accept Source # | |
HasOptionalParam ReadClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReadClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReadClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReadClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ReadClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadClusterRole contentType res accept -> Pretty -> KubernetesRequest ReadClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ReadClusterRole contentType res accept -> Pretty -> KubernetesRequest ReadClusterRole contentType res accept Source # | |
HasOptionalParam PatchNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam PatchNamespacedRoleBinding Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> Force -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> Force -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam PatchNamespacedRoleBinding FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam PatchNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam PatchNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRole contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRole contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedRole contentType res accept Source # | |
HasOptionalParam PatchNamespacedRole Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRole contentType res accept -> Force -> KubernetesRequest PatchNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRole contentType res accept -> Force -> KubernetesRequest PatchNamespacedRole contentType res accept Source # | |
HasOptionalParam PatchNamespacedRole FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedRole contentType res accept Source # | |
HasOptionalParam PatchNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRole contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRole contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedRole contentType res accept Source # | |
HasOptionalParam PatchClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # | |
HasOptionalParam PatchClusterRoleBinding Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> Force -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> Force -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # | |
HasOptionalParam PatchClusterRoleBinding FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # | |
HasOptionalParam PatchClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # | |
HasOptionalParam PatchClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRole contentType res accept -> Pretty -> KubernetesRequest PatchClusterRole contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRole contentType res accept -> Pretty -> KubernetesRequest PatchClusterRole contentType res accept Source # | |
HasOptionalParam PatchClusterRole Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRole contentType res accept -> Force -> KubernetesRequest PatchClusterRole contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRole contentType res accept -> Force -> KubernetesRequest PatchClusterRole contentType res accept Source # | |
HasOptionalParam PatchClusterRole FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRole contentType res accept -> FieldManager -> KubernetesRequest PatchClusterRole contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRole contentType res accept -> FieldManager -> KubernetesRequest PatchClusterRole contentType res accept Source # | |
HasOptionalParam PatchClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRole contentType res accept -> DryRun -> KubernetesRequest PatchClusterRole contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRole contentType res accept -> DryRun -> KubernetesRequest PatchClusterRole contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Watch -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Watch -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Limit -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Limit -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Continue -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Continue -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRole Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> Watch -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> Watch -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> Limit -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> Limit -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> Continue -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> Continue -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Watch -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Watch -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Limit -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Limit -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Continue -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Continue -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRole Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> Watch -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> Watch -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> Pretty -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> Pretty -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> Limit -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> Limit -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> LabelSelector -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> LabelSelector -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> FieldSelector -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> FieldSelector -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> Continue -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> Continue -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Limit -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Limit -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Continue -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Continue -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Limit -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Limit -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Continue -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Continue -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRole PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> Pretty -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> Pretty -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRole OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRole GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> DryRun -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> DryRun -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam CreateNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedRoleBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRole contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRole contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedRole contentType res accept Source # | |
HasOptionalParam CreateNamespacedRole FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedRole contentType res accept Source # | |
HasOptionalParam CreateNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRole contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRole contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedRole contentType res accept Source # | |
HasOptionalParam CreateClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # | |
HasOptionalParam CreateClusterRoleBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # | |
HasOptionalParam CreateClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # | |
HasOptionalParam CreateClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRole contentType res accept -> Pretty -> KubernetesRequest CreateClusterRole contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRole contentType res accept -> Pretty -> KubernetesRequest CreateClusterRole contentType res accept Source # | |
HasOptionalParam CreateClusterRole FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRole contentType res accept -> FieldManager -> KubernetesRequest CreateClusterRole contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRole contentType res accept -> FieldManager -> KubernetesRequest CreateClusterRole contentType res accept Source # | |
HasOptionalParam CreateClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRole contentType res accept -> DryRun -> KubernetesRequest CreateClusterRole contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRole contentType res accept -> DryRun -> KubernetesRequest CreateClusterRole contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRoleBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRole FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # | |
HasOptionalParam ReplaceClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceClusterRoleBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRole contentType res accept -> Pretty -> KubernetesRequest ReplaceClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRole contentType res accept -> Pretty -> KubernetesRequest ReplaceClusterRole contentType res accept Source # | |
HasOptionalParam ReplaceClusterRole FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRole contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRole contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterRole contentType res accept Source # | |
HasOptionalParam ReplaceClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRole contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRole contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterRole contentType res accept Source # | |
HasOptionalParam ReadNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ReadNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedRole contentType res accept Source # | |
HasOptionalParam ReadClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReadClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReadClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReadClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ReadClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadClusterRole contentType res accept -> Pretty -> KubernetesRequest ReadClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ReadClusterRole contentType res accept -> Pretty -> KubernetesRequest ReadClusterRole contentType res accept Source # | |
HasOptionalParam PatchNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam PatchNamespacedRoleBinding Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> Force -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> Force -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam PatchNamespacedRoleBinding FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam PatchNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam PatchNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRole contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRole contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedRole contentType res accept Source # | |
HasOptionalParam PatchNamespacedRole Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRole contentType res accept -> Force -> KubernetesRequest PatchNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRole contentType res accept -> Force -> KubernetesRequest PatchNamespacedRole contentType res accept Source # | |
HasOptionalParam PatchNamespacedRole FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedRole contentType res accept Source # | |
HasOptionalParam PatchNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRole contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRole contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedRole contentType res accept Source # | |
HasOptionalParam PatchClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # | |
HasOptionalParam PatchClusterRoleBinding Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> Force -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> Force -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # | |
HasOptionalParam PatchClusterRoleBinding FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # | |
HasOptionalParam PatchClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # | |
HasOptionalParam PatchClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRole contentType res accept -> Pretty -> KubernetesRequest PatchClusterRole contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRole contentType res accept -> Pretty -> KubernetesRequest PatchClusterRole contentType res accept Source # | |
HasOptionalParam PatchClusterRole Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRole contentType res accept -> Force -> KubernetesRequest PatchClusterRole contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRole contentType res accept -> Force -> KubernetesRequest PatchClusterRole contentType res accept Source # | |
HasOptionalParam PatchClusterRole FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRole contentType res accept -> FieldManager -> KubernetesRequest PatchClusterRole contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRole contentType res accept -> FieldManager -> KubernetesRequest PatchClusterRole contentType res accept Source # | |
HasOptionalParam PatchClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRole contentType res accept -> DryRun -> KubernetesRequest PatchClusterRole contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRole contentType res accept -> DryRun -> KubernetesRequest PatchClusterRole contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Watch -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Watch -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Limit -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Limit -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Continue -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Continue -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRole Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> Watch -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> Watch -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> Limit -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> Limit -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> Continue -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> Continue -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Watch -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Watch -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Limit -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Limit -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Continue -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Continue -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRole Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> Watch -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> Watch -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> Pretty -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> Pretty -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> Limit -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> Limit -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> LabelSelector -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> LabelSelector -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> FieldSelector -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> FieldSelector -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> Continue -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> Continue -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Limit -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Limit -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Continue -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Continue -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Limit -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Limit -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Continue -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Continue -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRole PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> Pretty -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> Pretty -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRole OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRole GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> DryRun -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> DryRun -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam CreateNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedRoleBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRole contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRole contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedRole contentType res accept Source # | |
HasOptionalParam CreateNamespacedRole FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedRole contentType res accept Source # | |
HasOptionalParam CreateNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRole contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRole contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedRole contentType res accept Source # | |
HasOptionalParam CreateClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # | |
HasOptionalParam CreateClusterRoleBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # | |
HasOptionalParam CreateClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # | |
HasOptionalParam CreateClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRole contentType res accept -> Pretty -> KubernetesRequest CreateClusterRole contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRole contentType res accept -> Pretty -> KubernetesRequest CreateClusterRole contentType res accept Source # | |
HasOptionalParam CreateClusterRole FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRole contentType res accept -> FieldManager -> KubernetesRequest CreateClusterRole contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRole contentType res accept -> FieldManager -> KubernetesRequest CreateClusterRole contentType res accept Source # | |
HasOptionalParam CreateClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRole contentType res accept -> DryRun -> KubernetesRequest CreateClusterRole contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRole contentType res accept -> DryRun -> KubernetesRequest CreateClusterRole contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRoleBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRole FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedRole contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedRole contentType res accept Source # | |
HasOptionalParam ReplaceClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceClusterRoleBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ReplaceClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRole contentType res accept -> Pretty -> KubernetesRequest ReplaceClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRole contentType res accept -> Pretty -> KubernetesRequest ReplaceClusterRole contentType res accept Source # | |
HasOptionalParam ReplaceClusterRole FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRole contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRole contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterRole contentType res accept Source # | |
HasOptionalParam ReplaceClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceClusterRole contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterRole contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterRole contentType res accept Source # | |
HasOptionalParam ReadNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ReadNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedRole contentType res accept Source # | |
HasOptionalParam ReadClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReadClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReadClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ReadClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ReadClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ReadClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ReadClusterRole contentType res accept -> Pretty -> KubernetesRequest ReadClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ReadClusterRole contentType res accept -> Pretty -> KubernetesRequest ReadClusterRole contentType res accept Source # | |
HasOptionalParam PatchNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam PatchNamespacedRoleBinding Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> Force -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> Force -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam PatchNamespacedRoleBinding FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam PatchNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam PatchNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRole contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRole contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedRole contentType res accept Source # | |
HasOptionalParam PatchNamespacedRole Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRole contentType res accept -> Force -> KubernetesRequest PatchNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRole contentType res accept -> Force -> KubernetesRequest PatchNamespacedRole contentType res accept Source # | |
HasOptionalParam PatchNamespacedRole FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedRole contentType res accept Source # | |
HasOptionalParam PatchNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedRole contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedRole contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedRole contentType res accept Source # | |
HasOptionalParam PatchClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # | |
HasOptionalParam PatchClusterRoleBinding Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> Force -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> Force -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # | |
HasOptionalParam PatchClusterRoleBinding FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # | |
HasOptionalParam PatchClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest PatchClusterRoleBinding contentType res accept Source # | |
HasOptionalParam PatchClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRole contentType res accept -> Pretty -> KubernetesRequest PatchClusterRole contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRole contentType res accept -> Pretty -> KubernetesRequest PatchClusterRole contentType res accept Source # | |
HasOptionalParam PatchClusterRole Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRole contentType res accept -> Force -> KubernetesRequest PatchClusterRole contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRole contentType res accept -> Force -> KubernetesRequest PatchClusterRole contentType res accept Source # | |
HasOptionalParam PatchClusterRole FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRole contentType res accept -> FieldManager -> KubernetesRequest PatchClusterRole contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRole contentType res accept -> FieldManager -> KubernetesRequest PatchClusterRole contentType res accept Source # | |
HasOptionalParam PatchClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest PatchClusterRole contentType res accept -> DryRun -> KubernetesRequest PatchClusterRole contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterRole contentType res accept -> DryRun -> KubernetesRequest PatchClusterRole contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRoleForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListRoleBindingForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRoleBindingForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Watch -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Watch -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Limit -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Limit -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Continue -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> Continue -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRoleBinding AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRoleBinding contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam ListNamespacedRole Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> Watch -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> Watch -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> Pretty -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> Limit -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> Limit -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> Continue -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> Continue -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListNamespacedRole AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedRole contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedRole contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedRole contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Watch -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Watch -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Limit -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Limit -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Continue -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> Continue -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRoleBinding AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRoleBinding contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRoleBinding contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListClusterRoleBinding contentType res accept Source # | |
HasOptionalParam ListClusterRole Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> Watch -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> Watch -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> Pretty -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> Pretty -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> Limit -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> Limit -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> LabelSelector -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> LabelSelector -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> FieldSelector -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> FieldSelector -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> Continue -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> Continue -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam ListClusterRole AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest ListClusterRole contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListClusterRole contentType res accept Source # (-&-) :: KubernetesRequest ListClusterRole contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListClusterRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedRole contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedRole contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRoleBinding Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedRole Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedRole contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Limit -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Limit -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRoleBinding Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Continue -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept -> Continue -> KubernetesRequest DeleteCollectionClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Limit -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Limit -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterRole Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Continue -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterRole contentType res accept -> Continue -> KubernetesRequest DeleteCollectionClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest DeleteClusterRoleBinding contentType res accept Source # | |
HasOptionalParam DeleteClusterRole PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> Pretty -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> Pretty -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRole OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRole GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam DeleteClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest DeleteClusterRole contentType res accept -> DryRun -> KubernetesRequest DeleteClusterRole contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterRole contentType res accept -> DryRun -> KubernetesRequest DeleteClusterRole contentType res accept Source # | |
HasOptionalParam CreateNamespacedRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedRoleBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRoleBinding contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedRoleBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRole contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRole contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedRole contentType res accept Source # | |
HasOptionalParam CreateNamespacedRole FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRole contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedRole contentType res accept Source # | |
HasOptionalParam CreateNamespacedRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedRole contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedRole contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedRole contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedRole contentType res accept Source # | |
HasOptionalParam CreateClusterRoleBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> Pretty -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # | |
HasOptionalParam CreateClusterRoleBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> FieldManager -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # | |
HasOptionalParam CreateClusterRoleBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRoleBinding contentType res accept -> DryRun -> KubernetesRequest CreateClusterRoleBinding contentType res accept Source # | |
HasOptionalParam CreateClusterRole Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRole contentType res accept -> Pretty -> KubernetesRequest CreateClusterRole contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRole contentType res accept -> Pretty -> KubernetesRequest CreateClusterRole contentType res accept Source # | |
HasOptionalParam CreateClusterRole FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRole contentType res accept -> FieldManager -> KubernetesRequest CreateClusterRole contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRole contentType res accept -> FieldManager -> KubernetesRequest CreateClusterRole contentType res accept Source # | |
HasOptionalParam CreateClusterRole DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.RbacAuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateClusterRole contentType res accept -> DryRun -> KubernetesRequest CreateClusterRole contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterRole contentType res accept -> DryRun -> KubernetesRequest CreateClusterRole contentType res accept Source # | |
HasOptionalParam ReplacePodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplacePodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest ReplacePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReplacePodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest ReplacePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ReplacePodSecurityPolicy FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplacePodSecurityPolicy contentType res accept -> FieldManager -> KubernetesRequest ReplacePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReplacePodSecurityPolicy contentType res accept -> FieldManager -> KubernetesRequest ReplacePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ReplacePodSecurityPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplacePodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest ReplacePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReplacePodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest ReplacePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodDisruptionBudgetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodDisruptionBudgetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPodDisruptionBudgetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodDisruptionBudgetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPodDisruptionBudgetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodDisruptionBudgetStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodDisruptionBudgetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPodDisruptionBudgetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodDisruptionBudgetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPodDisruptionBudgetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodDisruptionBudgetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodDisruptionBudgetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPodDisruptionBudgetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodDisruptionBudgetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPodDisruptionBudgetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodDisruptionBudget Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodDisruptionBudget FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodDisruptionBudget contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodDisruptionBudget contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodDisruptionBudget DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodDisruptionBudget contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodDisruptionBudget contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ReadPodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest ReadPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReadPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest ReadPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ReadPodSecurityPolicy Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadPodSecurityPolicy contentType res accept -> Export -> KubernetesRequest ReadPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReadPodSecurityPolicy contentType res accept -> Export -> KubernetesRequest ReadPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ReadPodSecurityPolicy Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadPodSecurityPolicy contentType res accept -> Exact -> KubernetesRequest ReadPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReadPodSecurityPolicy contentType res accept -> Exact -> KubernetesRequest ReadPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodDisruptionBudgetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodDisruptionBudgetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPodDisruptionBudgetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodDisruptionBudgetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPodDisruptionBudgetStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodDisruptionBudget Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodDisruptionBudget Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodDisruptionBudget contentType res accept -> Export -> KubernetesRequest ReadNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodDisruptionBudget contentType res accept -> Export -> KubernetesRequest ReadNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodDisruptionBudget Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodDisruptionBudget contentType res accept -> Exact -> KubernetesRequest ReadNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodDisruptionBudget contentType res accept -> Exact -> KubernetesRequest ReadNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam PatchPodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam PatchPodSecurityPolicy Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> Force -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> Force -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam PatchPodSecurityPolicy FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> FieldManager -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> FieldManager -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam PatchPodSecurityPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodDisruptionBudgetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodDisruptionBudgetStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodDisruptionBudgetStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodDisruptionBudgetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPodDisruptionBudgetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodDisruptionBudget Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodDisruptionBudget Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept -> Force -> KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept -> Force -> KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodDisruptionBudget FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodDisruptionBudget DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Watch -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Watch -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> ResourceVersion -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> ResourceVersion -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Limit -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Limit -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> LabelSelector -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> LabelSelector -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> FieldSelector -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> FieldSelector -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Continue -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Continue -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodDisruptionBudgetForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodDisruptionBudgetForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodDisruptionBudgetForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodDisruptionBudgetForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodDisruptionBudgetForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodDisruptionBudgetForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodDisruptionBudgetForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodDisruptionBudgetForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodDisruptionBudgetForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPodDisruptionBudgetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNamespacedPodDisruptionBudget Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> Watch -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> Watch -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ListNamespacedPodDisruptionBudget TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ListNamespacedPodDisruptionBudget ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ListNamespacedPodDisruptionBudget Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ListNamespacedPodDisruptionBudget Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> Limit -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> Limit -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ListNamespacedPodDisruptionBudget LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ListNamespacedPodDisruptionBudget FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ListNamespacedPodDisruptionBudget Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> Continue -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> Continue -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ListNamespacedPodDisruptionBudget AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeletePodSecurityPolicy PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeletePodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeletePodSecurityPolicy OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeletePodSecurityPolicy GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeletePodSecurityPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodDisruptionBudget PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodDisruptionBudget Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodDisruptionBudget OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodDisruptionBudget GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodDisruptionBudget DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> Limit -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> Limit -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> Continue -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> Continue -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodDisruptionBudget TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodDisruptionBudget ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodDisruptionBudget PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodDisruptionBudget Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodDisruptionBudget OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodDisruptionBudget Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodDisruptionBudget LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodDisruptionBudget GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodDisruptionBudget FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodDisruptionBudget DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodDisruptionBudget Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam CreatePodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest CreatePodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest CreatePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest CreatePodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest CreatePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam CreatePodSecurityPolicy FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest CreatePodSecurityPolicy contentType res accept -> FieldManager -> KubernetesRequest CreatePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest CreatePodSecurityPolicy contentType res accept -> FieldManager -> KubernetesRequest CreatePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam CreatePodSecurityPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest CreatePodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest CreatePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest CreatePodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest CreatePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodDisruptionBudget Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodDisruptionBudget contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodDisruptionBudget FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodDisruptionBudget contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodDisruptionBudget contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodDisruptionBudget DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.PolicyV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodDisruptionBudget contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPodDisruptionBudget contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodDisruptionBudget contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPodDisruptionBudget contentType res accept Source # | |
HasOptionalParam ReplaceRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceRuntimeClass contentType res accept -> Pretty -> KubernetesRequest ReplaceRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ReplaceRuntimeClass contentType res accept -> Pretty -> KubernetesRequest ReplaceRuntimeClass contentType res accept Source # | |
HasOptionalParam ReplaceRuntimeClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceRuntimeClass contentType res accept -> FieldManager -> KubernetesRequest ReplaceRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ReplaceRuntimeClass contentType res accept -> FieldManager -> KubernetesRequest ReplaceRuntimeClass contentType res accept Source # | |
HasOptionalParam ReplaceRuntimeClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceRuntimeClass contentType res accept -> DryRun -> KubernetesRequest ReplaceRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ReplaceRuntimeClass contentType res accept -> DryRun -> KubernetesRequest ReplaceRuntimeClass contentType res accept Source # | |
HasOptionalParam ReadRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadRuntimeClass contentType res accept -> Pretty -> KubernetesRequest ReadRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ReadRuntimeClass contentType res accept -> Pretty -> KubernetesRequest ReadRuntimeClass contentType res accept Source # | |
HasOptionalParam ReadRuntimeClass Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadRuntimeClass contentType res accept -> Export -> KubernetesRequest ReadRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ReadRuntimeClass contentType res accept -> Export -> KubernetesRequest ReadRuntimeClass contentType res accept Source # | |
HasOptionalParam ReadRuntimeClass Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadRuntimeClass contentType res accept -> Exact -> KubernetesRequest ReadRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ReadRuntimeClass contentType res accept -> Exact -> KubernetesRequest ReadRuntimeClass contentType res accept Source # | |
HasOptionalParam PatchRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchRuntimeClass contentType res accept -> Pretty -> KubernetesRequest PatchRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest PatchRuntimeClass contentType res accept -> Pretty -> KubernetesRequest PatchRuntimeClass contentType res accept Source # | |
HasOptionalParam PatchRuntimeClass Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchRuntimeClass contentType res accept -> Force -> KubernetesRequest PatchRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest PatchRuntimeClass contentType res accept -> Force -> KubernetesRequest PatchRuntimeClass contentType res accept Source # | |
HasOptionalParam PatchRuntimeClass FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchRuntimeClass contentType res accept -> FieldManager -> KubernetesRequest PatchRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest PatchRuntimeClass contentType res accept -> FieldManager -> KubernetesRequest PatchRuntimeClass contentType res accept Source # | |
HasOptionalParam PatchRuntimeClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchRuntimeClass contentType res accept -> DryRun -> KubernetesRequest PatchRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest PatchRuntimeClass contentType res accept -> DryRun -> KubernetesRequest PatchRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> Watch -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> Watch -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> ResourceVersion -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> ResourceVersion -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> Pretty -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> Pretty -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> Limit -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> Limit -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> LabelSelector -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> LabelSelector -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> FieldSelector -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> FieldSelector -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> Continue -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> Continue -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteRuntimeClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteRuntimeClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteRuntimeClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteRuntimeClass contentType res accept -> Pretty -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteRuntimeClass contentType res accept -> Pretty -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteRuntimeClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteRuntimeClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteRuntimeClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteRuntimeClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteRuntimeClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteRuntimeClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteRuntimeClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteRuntimeClass contentType res accept -> DryRun -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteRuntimeClass contentType res accept -> DryRun -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam CreateRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateRuntimeClass contentType res accept -> Pretty -> KubernetesRequest CreateRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest CreateRuntimeClass contentType res accept -> Pretty -> KubernetesRequest CreateRuntimeClass contentType res accept Source # | |
HasOptionalParam CreateRuntimeClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateRuntimeClass contentType res accept -> FieldManager -> KubernetesRequest CreateRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest CreateRuntimeClass contentType res accept -> FieldManager -> KubernetesRequest CreateRuntimeClass contentType res accept Source # | |
HasOptionalParam CreateRuntimeClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateRuntimeClass contentType res accept -> DryRun -> KubernetesRequest CreateRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest CreateRuntimeClass contentType res accept -> DryRun -> KubernetesRequest CreateRuntimeClass contentType res accept Source # | |
HasOptionalParam ReplaceRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceRuntimeClass contentType res accept -> Pretty -> KubernetesRequest ReplaceRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ReplaceRuntimeClass contentType res accept -> Pretty -> KubernetesRequest ReplaceRuntimeClass contentType res accept Source # | |
HasOptionalParam ReplaceRuntimeClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceRuntimeClass contentType res accept -> FieldManager -> KubernetesRequest ReplaceRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ReplaceRuntimeClass contentType res accept -> FieldManager -> KubernetesRequest ReplaceRuntimeClass contentType res accept Source # | |
HasOptionalParam ReplaceRuntimeClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceRuntimeClass contentType res accept -> DryRun -> KubernetesRequest ReplaceRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ReplaceRuntimeClass contentType res accept -> DryRun -> KubernetesRequest ReplaceRuntimeClass contentType res accept Source # | |
HasOptionalParam ReadRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadRuntimeClass contentType res accept -> Pretty -> KubernetesRequest ReadRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ReadRuntimeClass contentType res accept -> Pretty -> KubernetesRequest ReadRuntimeClass contentType res accept Source # | |
HasOptionalParam ReadRuntimeClass Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadRuntimeClass contentType res accept -> Export -> KubernetesRequest ReadRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ReadRuntimeClass contentType res accept -> Export -> KubernetesRequest ReadRuntimeClass contentType res accept Source # | |
HasOptionalParam ReadRuntimeClass Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadRuntimeClass contentType res accept -> Exact -> KubernetesRequest ReadRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ReadRuntimeClass contentType res accept -> Exact -> KubernetesRequest ReadRuntimeClass contentType res accept Source # | |
HasOptionalParam PatchRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchRuntimeClass contentType res accept -> Pretty -> KubernetesRequest PatchRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest PatchRuntimeClass contentType res accept -> Pretty -> KubernetesRequest PatchRuntimeClass contentType res accept Source # | |
HasOptionalParam PatchRuntimeClass Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchRuntimeClass contentType res accept -> Force -> KubernetesRequest PatchRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest PatchRuntimeClass contentType res accept -> Force -> KubernetesRequest PatchRuntimeClass contentType res accept Source # | |
HasOptionalParam PatchRuntimeClass FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchRuntimeClass contentType res accept -> FieldManager -> KubernetesRequest PatchRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest PatchRuntimeClass contentType res accept -> FieldManager -> KubernetesRequest PatchRuntimeClass contentType res accept Source # | |
HasOptionalParam PatchRuntimeClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchRuntimeClass contentType res accept -> DryRun -> KubernetesRequest PatchRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest PatchRuntimeClass contentType res accept -> DryRun -> KubernetesRequest PatchRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> Watch -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> Watch -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> TimeoutSeconds -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> ResourceVersion -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> ResourceVersion -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> Pretty -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> Pretty -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> Limit -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> Limit -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> LabelSelector -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> LabelSelector -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> FieldSelector -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> FieldSelector -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> Continue -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> Continue -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam ListRuntimeClass AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListRuntimeClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest ListRuntimeClass contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteRuntimeClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteRuntimeClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteRuntimeClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteRuntimeClass contentType res accept -> Pretty -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteRuntimeClass contentType res accept -> Pretty -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteRuntimeClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteRuntimeClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteRuntimeClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteRuntimeClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteRuntimeClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteRuntimeClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteRuntimeClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteRuntimeClass contentType res accept -> DryRun -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteRuntimeClass contentType res accept -> DryRun -> KubernetesRequest DeleteRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> Limit -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam DeleteCollectionRuntimeClass Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionRuntimeClass contentType res accept -> Continue -> KubernetesRequest DeleteCollectionRuntimeClass contentType res accept Source # | |
HasOptionalParam CreateRuntimeClass Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateRuntimeClass contentType res accept -> Pretty -> KubernetesRequest CreateRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest CreateRuntimeClass contentType res accept -> Pretty -> KubernetesRequest CreateRuntimeClass contentType res accept Source # | |
HasOptionalParam CreateRuntimeClass FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateRuntimeClass contentType res accept -> FieldManager -> KubernetesRequest CreateRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest CreateRuntimeClass contentType res accept -> FieldManager -> KubernetesRequest CreateRuntimeClass contentType res accept Source # | |
HasOptionalParam CreateRuntimeClass DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NodeV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateRuntimeClass contentType res accept -> DryRun -> KubernetesRequest CreateRuntimeClass contentType res accept Source # (-&-) :: KubernetesRequest CreateRuntimeClass contentType res accept -> DryRun -> KubernetesRequest CreateRuntimeClass contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedIngressStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedIngressStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedIngressStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedIngress contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedIngress FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedIngress contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedIngress contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedIngress contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedIngress DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedIngress contentType res accept Source # | |
HasOptionalParam ReadNamespacedIngressStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedIngressStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedIngressStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedIngress contentType res accept Source # | |
HasOptionalParam ReadNamespacedIngress Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedIngress contentType res accept -> Export -> KubernetesRequest ReadNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedIngress contentType res accept -> Export -> KubernetesRequest ReadNamespacedIngress contentType res accept Source # | |
HasOptionalParam ReadNamespacedIngress Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedIngress contentType res accept -> Exact -> KubernetesRequest ReadNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedIngress contentType res accept -> Exact -> KubernetesRequest ReadNamespacedIngress contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngressStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngressStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngressStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngressStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngress Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngress contentType res accept -> Force -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngress contentType res accept -> Force -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngress FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngress contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngress contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngress DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> Watch -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> Watch -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> Limit -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> Limit -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> Continue -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> Continue -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedIngress PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteNamespacedIngress OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteNamespacedIngress GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteNamespacedIngress DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam CreateNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedIngress contentType res accept Source # | |
HasOptionalParam CreateNamespacedIngress FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedIngress contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedIngress contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedIngress contentType res accept Source # | |
HasOptionalParam CreateNamespacedIngress DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedIngress contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedNetworkPolicy FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedNetworkPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ReadNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ReadNamespacedNetworkPolicy Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept -> Export -> KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept -> Export -> KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ReadNamespacedNetworkPolicy Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept -> Exact -> KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept -> Exact -> KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam PatchNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam PatchNamespacedNetworkPolicy Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> Force -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> Force -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam PatchNamespacedNetworkPolicy FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam PatchNamespacedNetworkPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Watch -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Watch -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Limit -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Limit -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Continue -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Continue -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteNamespacedNetworkPolicy PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteNamespacedNetworkPolicy OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteNamespacedNetworkPolicy GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteNamespacedNetworkPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam CreateNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam CreateNamespacedNetworkPolicy FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam CreateNamespacedNetworkPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.NetworkingV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ReplacePodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplacePodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest ReplacePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReplacePodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest ReplacePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ReplacePodSecurityPolicy FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplacePodSecurityPolicy contentType res accept -> FieldManager -> KubernetesRequest ReplacePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReplacePodSecurityPolicy contentType res accept -> FieldManager -> KubernetesRequest ReplacePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ReplacePodSecurityPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplacePodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest ReplacePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReplacePodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest ReplacePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicationControllerDummyScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicationControllerDummyScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicationControllerDummyScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicationControllerDummyScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicationControllerDummyScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicationControllerDummyScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicationControllerDummyScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicationControllerDummyScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicationControllerDummyScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicationControllerDummyScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicationControllerDummyScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicationControllerDummyScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicationControllerDummyScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicationControllerDummyScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicationControllerDummyScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedNetworkPolicy FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedNetworkPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedIngressStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedIngressStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedIngressStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedIngress contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedIngress FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedIngress contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedIngress contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedIngress contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedIngress DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedIngress contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeployment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSetStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReadPodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest ReadPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReadPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest ReadPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ReadPodSecurityPolicy Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadPodSecurityPolicy contentType res accept -> Export -> KubernetesRequest ReadPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReadPodSecurityPolicy contentType res accept -> Export -> KubernetesRequest ReadPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ReadPodSecurityPolicy Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadPodSecurityPolicy contentType res accept -> Exact -> KubernetesRequest ReadPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReadPodSecurityPolicy contentType res accept -> Exact -> KubernetesRequest ReadPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicationControllerDummyScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicationControllerDummyScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicationControllerDummyScale contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicationControllerDummyScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicationControllerDummyScale contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSet Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSet Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ReadNamespacedNetworkPolicy Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept -> Export -> KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept -> Export -> KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ReadNamespacedNetworkPolicy Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept -> Exact -> KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept -> Exact -> KubernetesRequest ReadNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ReadNamespacedIngressStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedIngressStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedIngressStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedIngress contentType res accept Source # | |
HasOptionalParam ReadNamespacedIngress Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedIngress contentType res accept -> Export -> KubernetesRequest ReadNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedIngress contentType res accept -> Export -> KubernetesRequest ReadNamespacedIngress contentType res accept Source # | |
HasOptionalParam ReadNamespacedIngress Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedIngress contentType res accept -> Exact -> KubernetesRequest ReadNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedIngress contentType res accept -> Exact -> KubernetesRequest ReadNamespacedIngress contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeploymentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeploymentScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeployment Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Export -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Export -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeployment Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReadNamespacedDaemonSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedDaemonSet Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedDaemonSet Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam PatchPodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam PatchPodSecurityPolicy Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> Force -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> Force -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam PatchPodSecurityPolicy FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> FieldManager -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> FieldManager -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam PatchPodSecurityPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchPodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest PatchPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationControllerDummyScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationControllerDummyScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationControllerDummyScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationControllerDummyScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicationControllerDummyScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSet Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSet FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam PatchNamespacedNetworkPolicy Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> Force -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> Force -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam PatchNamespacedNetworkPolicy FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam PatchNamespacedNetworkPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngressStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngressStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngressStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngressStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngressStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedIngressStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngress Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngress contentType res accept -> Force -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngress contentType res accept -> Force -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngress FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngress contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngress contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # | |
HasOptionalParam PatchNamespacedIngress DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedIngress contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSetStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSetStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSet Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSet FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Watch -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Watch -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> ResourceVersion -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> ResourceVersion -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Limit -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Limit -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> LabelSelector -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> LabelSelector -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> FieldSelector -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> FieldSelector -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Continue -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> Continue -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListPodSecurityPolicy AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListPodSecurityPolicy contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNetworkPolicyForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNetworkPolicyForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Watch -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Watch -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Limit -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Limit -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Continue -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> Continue -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedNetworkPolicy AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedNetworkPolicy contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> Watch -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> Watch -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> Limit -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> Limit -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> Continue -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> Continue -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedIngress AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedIngress contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedIngress contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedIngress contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Watch -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Watch -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListIngressForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListIngressForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListIngressForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeletePodSecurityPolicy PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeletePodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeletePodSecurityPolicy OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeletePodSecurityPolicy GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeletePodSecurityPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeletePodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest DeletePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedNetworkPolicy PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteNamespacedNetworkPolicy OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteNamespacedNetworkPolicy GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteNamespacedNetworkPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteNamespacedIngress PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteNamespacedIngress OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteNamespacedIngress GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteNamespacedIngress DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> Limit -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> Limit -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionPodSecurityPolicy Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> Continue -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept -> Continue -> KubernetesRequest DeleteCollectionPodSecurityPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedNetworkPolicy Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedIngress Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedIngress contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam CreatePodSecurityPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreatePodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest CreatePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest CreatePodSecurityPolicy contentType res accept -> Pretty -> KubernetesRequest CreatePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam CreatePodSecurityPolicy FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreatePodSecurityPolicy contentType res accept -> FieldManager -> KubernetesRequest CreatePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest CreatePodSecurityPolicy contentType res accept -> FieldManager -> KubernetesRequest CreatePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam CreatePodSecurityPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreatePodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest CreatePodSecurityPolicy contentType res accept Source # (-&-) :: KubernetesRequest CreatePodSecurityPolicy contentType res accept -> DryRun -> KubernetesRequest CreatePodSecurityPolicy contentType res accept Source # | |
HasOptionalParam CreateNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedReplicaSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedNetworkPolicy Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam CreateNamespacedNetworkPolicy FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam CreateNamespacedNetworkPolicy DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedNetworkPolicy contentType res accept Source # | |
HasOptionalParam CreateNamespacedIngress Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedIngress contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedIngress contentType res accept Source # | |
HasOptionalParam CreateNamespacedIngress FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedIngress contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedIngress contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedIngress contentType res accept Source # | |
HasOptionalParam CreateNamespacedIngress DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedIngress contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedIngress contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedIngress contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeploymentRollback Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeploymentRollback FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeploymentRollback DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeployment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # | |
HasOptionalParam CreateNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedDaemonSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ExtensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedEvent contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedEvent FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedEvent contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedEvent contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedEvent contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedEvent DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedEvent contentType res accept Source # | |
HasOptionalParam ReadNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedEvent contentType res accept Source # | |
HasOptionalParam ReadNamespacedEvent Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedEvent contentType res accept -> Export -> KubernetesRequest ReadNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedEvent contentType res accept -> Export -> KubernetesRequest ReadNamespacedEvent contentType res accept Source # | |
HasOptionalParam ReadNamespacedEvent Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedEvent contentType res accept -> Exact -> KubernetesRequest ReadNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedEvent contentType res accept -> Exact -> KubernetesRequest ReadNamespacedEvent contentType res accept Source # | |
HasOptionalParam PatchNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # | |
HasOptionalParam PatchNamespacedEvent Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEvent contentType res accept -> Force -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEvent contentType res accept -> Force -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # | |
HasOptionalParam PatchNamespacedEvent FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEvent contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEvent contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # | |
HasOptionalParam PatchNamespacedEvent DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> Watch -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> Watch -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> Limit -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> Limit -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> Continue -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> Continue -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEvent PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEvent OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEvent GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEvent DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam CreateNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedEvent contentType res accept Source # | |
HasOptionalParam CreateNamespacedEvent FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedEvent contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedEvent contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedEvent contentType res accept Source # | |
HasOptionalParam CreateNamespacedEvent DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.EventsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedEvent contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedEndpointSlice Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedEndpointSlice FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedEndpointSlice contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedEndpointSlice contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedEndpointSlice DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedEndpointSlice contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedEndpointSlice contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ReadNamespacedEndpointSlice Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ReadNamespacedEndpointSlice Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedEndpointSlice contentType res accept -> Export -> KubernetesRequest ReadNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedEndpointSlice contentType res accept -> Export -> KubernetesRequest ReadNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ReadNamespacedEndpointSlice Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedEndpointSlice contentType res accept -> Exact -> KubernetesRequest ReadNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedEndpointSlice contentType res accept -> Exact -> KubernetesRequest ReadNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam PatchNamespacedEndpointSlice Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam PatchNamespacedEndpointSlice Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEndpointSlice contentType res accept -> Force -> KubernetesRequest PatchNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEndpointSlice contentType res accept -> Force -> KubernetesRequest PatchNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam PatchNamespacedEndpointSlice FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEndpointSlice contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEndpointSlice contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam PatchNamespacedEndpointSlice DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEndpointSlice contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEndpointSlice contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpointSlice Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> Watch -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> Watch -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpointSlice TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpointSlice ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpointSlice Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpointSlice Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> Limit -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> Limit -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpointSlice LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpointSlice FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpointSlice Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> Continue -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> Continue -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpointSlice AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpointSlice contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ListEndpointSliceForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointSliceForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointSliceForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointSliceForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointSliceForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointSliceForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointSliceForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointSliceForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointSliceForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListEndpointSliceForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEndpointSlice PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEndpointSlice Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEndpointSlice OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEndpointSlice GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEndpointSlice DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpointSlice TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpointSlice ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpointSlice PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpointSlice Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpointSlice OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpointSlice Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpointSlice LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpointSlice GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpointSlice FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpointSlice DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpointSlice Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam CreateNamespacedEndpointSlice Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedEndpointSlice contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam CreateNamespacedEndpointSlice FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedEndpointSlice contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedEndpointSlice contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam CreateNamespacedEndpointSlice DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.DiscoveryV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedEndpointSlice contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedEndpointSlice contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedEndpointSlice contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedEndpointSlice contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCustomObjectStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCustomObjectStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCustomObjectStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCustomObjectStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCustomObjectStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCustomObjectStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCustomObjectStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCustomObjectStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCustomObjectStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCustomObjectStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCustomObjectScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCustomObjectScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCustomObjectScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCustomObjectScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCustomObjectScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCustomObjectScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCustomObjectScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCustomObjectScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCustomObjectScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCustomObjectScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCustomObject FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCustomObject contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCustomObject contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCustomObject DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCustomObject contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCustomObject contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam ReplaceClusterCustomObjectStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ReplaceClusterCustomObjectStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterCustomObjectStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterCustomObjectStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterCustomObjectStatus contentType res accept Source # | |
HasOptionalParam ReplaceClusterCustomObjectStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ReplaceClusterCustomObjectStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterCustomObjectStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterCustomObjectStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterCustomObjectStatus contentType res accept Source # | |
HasOptionalParam ReplaceClusterCustomObjectScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ReplaceClusterCustomObjectScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterCustomObjectScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterCustomObjectScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterCustomObjectScale contentType res accept Source # | |
HasOptionalParam ReplaceClusterCustomObjectScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ReplaceClusterCustomObjectScale contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterCustomObjectScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterCustomObjectScale contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterCustomObjectScale contentType res accept Source # | |
HasOptionalParam ReplaceClusterCustomObject FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ReplaceClusterCustomObject contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterCustomObject contentType res accept -> FieldManager -> KubernetesRequest ReplaceClusterCustomObject contentType res accept Source # | |
HasOptionalParam ReplaceClusterCustomObject DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ReplaceClusterCustomObject contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ReplaceClusterCustomObject contentType res accept -> DryRun -> KubernetesRequest ReplaceClusterCustomObject contentType res accept Source # | |
HasOptionalParam PatchNamespacedCustomObjectStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCustomObjectStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedCustomObjectStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCustomObjectStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedCustomObjectStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedCustomObjectStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCustomObjectStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCustomObjectStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCustomObjectStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCustomObjectStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedCustomObjectStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCustomObjectStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCustomObjectStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCustomObjectStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCustomObjectStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedCustomObjectScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCustomObjectScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedCustomObjectScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCustomObjectScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedCustomObjectScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedCustomObjectScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCustomObjectScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCustomObjectScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCustomObjectScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCustomObjectScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedCustomObjectScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCustomObjectScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCustomObjectScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCustomObjectScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCustomObjectScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedCustomObject Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCustomObject contentType res accept -> Force -> KubernetesRequest PatchNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCustomObject contentType res accept -> Force -> KubernetesRequest PatchNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam PatchNamespacedCustomObject FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCustomObject contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCustomObject contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam PatchNamespacedCustomObject DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCustomObject contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCustomObject contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam PatchClusterCustomObjectStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchClusterCustomObjectStatus contentType res accept -> Force -> KubernetesRequest PatchClusterCustomObjectStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterCustomObjectStatus contentType res accept -> Force -> KubernetesRequest PatchClusterCustomObjectStatus contentType res accept Source # | |
HasOptionalParam PatchClusterCustomObjectStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchClusterCustomObjectStatus contentType res accept -> FieldManager -> KubernetesRequest PatchClusterCustomObjectStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterCustomObjectStatus contentType res accept -> FieldManager -> KubernetesRequest PatchClusterCustomObjectStatus contentType res accept Source # | |
HasOptionalParam PatchClusterCustomObjectStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchClusterCustomObjectStatus contentType res accept -> DryRun -> KubernetesRequest PatchClusterCustomObjectStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterCustomObjectStatus contentType res accept -> DryRun -> KubernetesRequest PatchClusterCustomObjectStatus contentType res accept Source # | |
HasOptionalParam PatchClusterCustomObjectScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchClusterCustomObjectScale contentType res accept -> Force -> KubernetesRequest PatchClusterCustomObjectScale contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterCustomObjectScale contentType res accept -> Force -> KubernetesRequest PatchClusterCustomObjectScale contentType res accept Source # | |
HasOptionalParam PatchClusterCustomObjectScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchClusterCustomObjectScale contentType res accept -> FieldManager -> KubernetesRequest PatchClusterCustomObjectScale contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterCustomObjectScale contentType res accept -> FieldManager -> KubernetesRequest PatchClusterCustomObjectScale contentType res accept Source # | |
HasOptionalParam PatchClusterCustomObjectScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchClusterCustomObjectScale contentType res accept -> DryRun -> KubernetesRequest PatchClusterCustomObjectScale contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterCustomObjectScale contentType res accept -> DryRun -> KubernetesRequest PatchClusterCustomObjectScale contentType res accept Source # | |
HasOptionalParam PatchClusterCustomObject Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchClusterCustomObject contentType res accept -> Force -> KubernetesRequest PatchClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterCustomObject contentType res accept -> Force -> KubernetesRequest PatchClusterCustomObject contentType res accept Source # | |
HasOptionalParam PatchClusterCustomObject FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchClusterCustomObject contentType res accept -> FieldManager -> KubernetesRequest PatchClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterCustomObject contentType res accept -> FieldManager -> KubernetesRequest PatchClusterCustomObject contentType res accept Source # | |
HasOptionalParam PatchClusterCustomObject DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest PatchClusterCustomObject contentType res accept -> DryRun -> KubernetesRequest PatchClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest PatchClusterCustomObject contentType res accept -> DryRun -> KubernetesRequest PatchClusterCustomObject contentType res accept Source # | |
HasOptionalParam ListNamespacedCustomObject Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> Watch -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> Watch -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam ListNamespacedCustomObject TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam ListNamespacedCustomObject ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam ListNamespacedCustomObject Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> Pretty -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> Pretty -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam ListNamespacedCustomObject Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> Limit -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> Limit -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam ListNamespacedCustomObject LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam ListNamespacedCustomObject FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam ListNamespacedCustomObject Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> Continue -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCustomObject contentType res accept -> Continue -> KubernetesRequest ListNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam ListClusterCustomObject Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept -> Watch -> KubernetesRequest ListClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListClusterCustomObject contentType res accept -> Watch -> KubernetesRequest ListClusterCustomObject contentType res accept Source # | |
HasOptionalParam ListClusterCustomObject TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListClusterCustomObject contentType res accept -> TimeoutSeconds -> KubernetesRequest ListClusterCustomObject contentType res accept Source # | |
HasOptionalParam ListClusterCustomObject ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListClusterCustomObject contentType res accept -> ResourceVersion -> KubernetesRequest ListClusterCustomObject contentType res accept Source # | |
HasOptionalParam ListClusterCustomObject Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept -> Pretty -> KubernetesRequest ListClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListClusterCustomObject contentType res accept -> Pretty -> KubernetesRequest ListClusterCustomObject contentType res accept Source # | |
HasOptionalParam ListClusterCustomObject Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept -> Limit -> KubernetesRequest ListClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListClusterCustomObject contentType res accept -> Limit -> KubernetesRequest ListClusterCustomObject contentType res accept Source # | |
HasOptionalParam ListClusterCustomObject LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept -> LabelSelector -> KubernetesRequest ListClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListClusterCustomObject contentType res accept -> LabelSelector -> KubernetesRequest ListClusterCustomObject contentType res accept Source # | |
HasOptionalParam ListClusterCustomObject FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept -> FieldSelector -> KubernetesRequest ListClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListClusterCustomObject contentType res accept -> FieldSelector -> KubernetesRequest ListClusterCustomObject contentType res accept Source # | |
HasOptionalParam ListClusterCustomObject Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest ListClusterCustomObject contentType res accept -> Continue -> KubernetesRequest ListClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest ListClusterCustomObject contentType res accept -> Continue -> KubernetesRequest ListClusterCustomObject contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCustomObject PropagationPolicy Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCustomObject contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCustomObject contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCustomObject OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCustomObject contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCustomObject contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCustomObject GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCustomObject contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCustomObject contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCustomObject DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCustomObject contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCustomObject contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCustomObject PropagationPolicy Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCustomObject Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCustomObject OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCustomObject GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCustomObject DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterCustomObject PropagationPolicy Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterCustomObject Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterCustomObject OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterCustomObject GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept Source # | |
HasOptionalParam DeleteCollectionClusterCustomObject DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionClusterCustomObject contentType res accept Source # | |
HasOptionalParam DeleteClusterCustomObject PropagationPolicy Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteClusterCustomObject contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterCustomObject contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteClusterCustomObject contentType res accept Source # | |
HasOptionalParam DeleteClusterCustomObject OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteClusterCustomObject contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterCustomObject contentType res accept -> OrphanDependents -> KubernetesRequest DeleteClusterCustomObject contentType res accept Source # | |
HasOptionalParam DeleteClusterCustomObject GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteClusterCustomObject contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterCustomObject contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteClusterCustomObject contentType res accept Source # | |
HasOptionalParam DeleteClusterCustomObject DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest DeleteClusterCustomObject contentType res accept -> DryRun -> KubernetesRequest DeleteClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest DeleteClusterCustomObject contentType res accept -> DryRun -> KubernetesRequest DeleteClusterCustomObject contentType res accept Source # | |
HasOptionalParam CreateNamespacedCustomObject Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest CreateNamespacedCustomObject contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedCustomObject contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam CreateNamespacedCustomObject FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest CreateNamespacedCustomObject contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedCustomObject contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam CreateNamespacedCustomObject DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest CreateNamespacedCustomObject contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedCustomObject contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedCustomObject contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedCustomObject contentType res accept Source # | |
HasOptionalParam CreateClusterCustomObject Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest CreateClusterCustomObject contentType res accept -> Pretty -> KubernetesRequest CreateClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterCustomObject contentType res accept -> Pretty -> KubernetesRequest CreateClusterCustomObject contentType res accept Source # | |
HasOptionalParam CreateClusterCustomObject FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest CreateClusterCustomObject contentType res accept -> FieldManager -> KubernetesRequest CreateClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterCustomObject contentType res accept -> FieldManager -> KubernetesRequest CreateClusterCustomObject contentType res accept Source # | |
HasOptionalParam CreateClusterCustomObject DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CustomObjects Methods applyOptionalParam :: KubernetesRequest CreateClusterCustomObject contentType res accept -> DryRun -> KubernetesRequest CreateClusterCustomObject contentType res accept Source # (-&-) :: KubernetesRequest CreateClusterCustomObject contentType res accept -> DryRun -> KubernetesRequest CreateClusterCustomObject contentType res accept Source # | |
HasOptionalParam ReplacePersistentVolumeStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplacePersistentVolumeStatus contentType res accept -> Pretty -> KubernetesRequest ReplacePersistentVolumeStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplacePersistentVolumeStatus contentType res accept -> Pretty -> KubernetesRequest ReplacePersistentVolumeStatus contentType res accept Source # | |
HasOptionalParam ReplacePersistentVolumeStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplacePersistentVolumeStatus contentType res accept -> FieldManager -> KubernetesRequest ReplacePersistentVolumeStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplacePersistentVolumeStatus contentType res accept -> FieldManager -> KubernetesRequest ReplacePersistentVolumeStatus contentType res accept Source # | |
HasOptionalParam ReplacePersistentVolumeStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplacePersistentVolumeStatus contentType res accept -> DryRun -> KubernetesRequest ReplacePersistentVolumeStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplacePersistentVolumeStatus contentType res accept -> DryRun -> KubernetesRequest ReplacePersistentVolumeStatus contentType res accept Source # | |
HasOptionalParam ReplacePersistentVolume Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplacePersistentVolume contentType res accept -> Pretty -> KubernetesRequest ReplacePersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ReplacePersistentVolume contentType res accept -> Pretty -> KubernetesRequest ReplacePersistentVolume contentType res accept Source # | |
HasOptionalParam ReplacePersistentVolume FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplacePersistentVolume contentType res accept -> FieldManager -> KubernetesRequest ReplacePersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ReplacePersistentVolume contentType res accept -> FieldManager -> KubernetesRequest ReplacePersistentVolume contentType res accept Source # | |
HasOptionalParam ReplacePersistentVolume DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplacePersistentVolume contentType res accept -> DryRun -> KubernetesRequest ReplacePersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ReplacePersistentVolume contentType res accept -> DryRun -> KubernetesRequest ReplacePersistentVolume contentType res accept Source # | |
HasOptionalParam ReplaceNodeStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNodeStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNodeStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNodeStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNodeStatus contentType res accept Source # | |
HasOptionalParam ReplaceNodeStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNodeStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNodeStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNodeStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNodeStatus contentType res accept Source # | |
HasOptionalParam ReplaceNodeStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNodeStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNodeStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNodeStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNodeStatus contentType res accept Source # | |
HasOptionalParam ReplaceNode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNode contentType res accept -> Pretty -> KubernetesRequest ReplaceNode contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNode contentType res accept -> Pretty -> KubernetesRequest ReplaceNode contentType res accept Source # | |
HasOptionalParam ReplaceNode FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNode contentType res accept -> FieldManager -> KubernetesRequest ReplaceNode contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNode contentType res accept -> FieldManager -> KubernetesRequest ReplaceNode contentType res accept Source # | |
HasOptionalParam ReplaceNode DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNode contentType res accept -> DryRun -> KubernetesRequest ReplaceNode contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNode contentType res accept -> DryRun -> KubernetesRequest ReplaceNode contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedServiceStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedServiceStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedServiceStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedServiceStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedServiceStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedServiceStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedServiceStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedServiceStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedServiceStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedServiceStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedServiceStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedServiceStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedServiceAccount Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedServiceAccount FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedServiceAccount contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedServiceAccount contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedServiceAccount DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedServiceAccount contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedServiceAccount contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedService contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedService contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedService contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedService FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedService contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedService contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedService contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedService contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedService contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedService contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedSecret Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedSecret contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedSecret FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedSecret contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedSecret contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedSecret contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedSecret DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedSecret contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedSecret contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedSecret contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedResourceQuotaStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedResourceQuotaStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedResourceQuotaStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedResourceQuotaStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedResourceQuota Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedResourceQuota FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedResourceQuota contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedResourceQuota contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedResourceQuota DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedResourceQuota contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedResourceQuota contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicationControllerStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicationControllerStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicationControllerStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicationControllerStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicationControllerScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicationControllerScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicationControllerScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicationControllerScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicationController Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicationController FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicationController contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicationController contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicationController DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicationController contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicationController contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodTemplate Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodTemplate FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodTemplate contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodTemplate contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodTemplate DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodTemplate contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodTemplate contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPodStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPodStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPodStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPodStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPodStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPodStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPodStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPodStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPodStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPod Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPod contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPod contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPod contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPod FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPod contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPod contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPod contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPod DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPod contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPod contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPod contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPersistentVolumeClaimStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPersistentVolumeClaimStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPersistentVolumeClaimStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaimStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPersistentVolumeClaim Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPersistentVolumeClaim FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedPersistentVolumeClaim DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedLimitRange Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedLimitRange FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedLimitRange contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedLimitRange contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedLimitRange DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedLimitRange contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedLimitRange contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedEvent contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedEvent FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedEvent contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedEvent contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedEvent contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedEvent DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedEvent contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedEndpoints Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedEndpoints FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedEndpoints contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedEndpoints contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedEndpoints DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedEndpoints contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedEndpoints contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedConfigMap Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedConfigMap FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedConfigMap contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedConfigMap contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedConfigMap DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedConfigMap contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedConfigMap contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ReplaceNamespaceStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespaceStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespaceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespaceStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespaceStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespaceStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespaceStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespaceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespaceStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespaceStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespaceStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespaceStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespaceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespaceStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespaceStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespaceFinalize Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespaceFinalize contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespaceFinalize contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespaceFinalize contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespaceFinalize contentType res accept Source # | |
HasOptionalParam ReplaceNamespaceFinalize FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespaceFinalize contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespaceFinalize contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespaceFinalize contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespaceFinalize contentType res accept Source # | |
HasOptionalParam ReplaceNamespaceFinalize DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespaceFinalize contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespaceFinalize contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespaceFinalize contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespaceFinalize contentType res accept Source # | |
HasOptionalParam ReplaceNamespace Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespace contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespace contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespace contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespace contentType res accept Source # | |
HasOptionalParam ReplaceNamespace FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespace contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespace contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespace contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespace contentType res accept Source # | |
HasOptionalParam ReplaceNamespace DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespace contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespace contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespace contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespace contentType res accept Source # | |
HasOptionalParam ReadPersistentVolumeStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadPersistentVolumeStatus contentType res accept -> Pretty -> KubernetesRequest ReadPersistentVolumeStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadPersistentVolumeStatus contentType res accept -> Pretty -> KubernetesRequest ReadPersistentVolumeStatus contentType res accept Source # | |
HasOptionalParam ReadPersistentVolume Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadPersistentVolume contentType res accept -> Pretty -> KubernetesRequest ReadPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ReadPersistentVolume contentType res accept -> Pretty -> KubernetesRequest ReadPersistentVolume contentType res accept Source # | |
HasOptionalParam ReadPersistentVolume Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadPersistentVolume contentType res accept -> Export -> KubernetesRequest ReadPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ReadPersistentVolume contentType res accept -> Export -> KubernetesRequest ReadPersistentVolume contentType res accept Source # | |
HasOptionalParam ReadPersistentVolume Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadPersistentVolume contentType res accept -> Exact -> KubernetesRequest ReadPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ReadPersistentVolume contentType res accept -> Exact -> KubernetesRequest ReadPersistentVolume contentType res accept Source # | |
HasOptionalParam ReadNodeStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNodeStatus contentType res accept -> Pretty -> KubernetesRequest ReadNodeStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNodeStatus contentType res accept -> Pretty -> KubernetesRequest ReadNodeStatus contentType res accept Source # | |
HasOptionalParam ReadNode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNode contentType res accept -> Pretty -> KubernetesRequest ReadNode contentType res accept Source # (-&-) :: KubernetesRequest ReadNode contentType res accept -> Pretty -> KubernetesRequest ReadNode contentType res accept Source # | |
HasOptionalParam ReadNode Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNode contentType res accept -> Export -> KubernetesRequest ReadNode contentType res accept Source # (-&-) :: KubernetesRequest ReadNode contentType res accept -> Export -> KubernetesRequest ReadNode contentType res accept Source # | |
HasOptionalParam ReadNode Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNode contentType res accept -> Exact -> KubernetesRequest ReadNode contentType res accept Source # (-&-) :: KubernetesRequest ReadNode contentType res accept -> Exact -> KubernetesRequest ReadNode contentType res accept Source # | |
HasOptionalParam ReadNamespacedServiceStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedServiceStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedServiceStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedServiceStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedServiceAccount Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ReadNamespacedServiceAccount Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedServiceAccount contentType res accept -> Export -> KubernetesRequest ReadNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedServiceAccount contentType res accept -> Export -> KubernetesRequest ReadNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ReadNamespacedServiceAccount Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedServiceAccount contentType res accept -> Exact -> KubernetesRequest ReadNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedServiceAccount contentType res accept -> Exact -> KubernetesRequest ReadNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ReadNamespacedService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedService contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedService contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedService contentType res accept Source # | |
HasOptionalParam ReadNamespacedService Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedService contentType res accept -> Export -> KubernetesRequest ReadNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedService contentType res accept -> Export -> KubernetesRequest ReadNamespacedService contentType res accept Source # | |
HasOptionalParam ReadNamespacedService Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedService contentType res accept -> Exact -> KubernetesRequest ReadNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedService contentType res accept -> Exact -> KubernetesRequest ReadNamespacedService contentType res accept Source # | |
HasOptionalParam ReadNamespacedSecret Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedSecret contentType res accept Source # | |
HasOptionalParam ReadNamespacedSecret Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedSecret contentType res accept -> Export -> KubernetesRequest ReadNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedSecret contentType res accept -> Export -> KubernetesRequest ReadNamespacedSecret contentType res accept Source # | |
HasOptionalParam ReadNamespacedSecret Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedSecret contentType res accept -> Exact -> KubernetesRequest ReadNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedSecret contentType res accept -> Exact -> KubernetesRequest ReadNamespacedSecret contentType res accept Source # | |
HasOptionalParam ReadNamespacedResourceQuotaStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedResourceQuotaStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedResourceQuotaStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedResourceQuotaStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedResourceQuotaStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedResourceQuota Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ReadNamespacedResourceQuota Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedResourceQuota contentType res accept -> Export -> KubernetesRequest ReadNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedResourceQuota contentType res accept -> Export -> KubernetesRequest ReadNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ReadNamespacedResourceQuota Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedResourceQuota contentType res accept -> Exact -> KubernetesRequest ReadNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedResourceQuota contentType res accept -> Exact -> KubernetesRequest ReadNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicationControllerStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicationControllerStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicationControllerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicationControllerStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicationControllerStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicationControllerScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicationControllerScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicationControllerScale contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicationControllerScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicationControllerScale contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicationController Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicationController Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicationController contentType res accept -> Export -> KubernetesRequest ReadNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicationController contentType res accept -> Export -> KubernetesRequest ReadNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicationController Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicationController contentType res accept -> Exact -> KubernetesRequest ReadNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicationController contentType res accept -> Exact -> KubernetesRequest ReadNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodTemplate Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodTemplate Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodTemplate contentType res accept -> Export -> KubernetesRequest ReadNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodTemplate contentType res accept -> Export -> KubernetesRequest ReadNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodTemplate Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodTemplate contentType res accept -> Exact -> KubernetesRequest ReadNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodTemplate contentType res accept -> Exact -> KubernetesRequest ReadNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPodStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPodStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodLog Timestamps Source # | Optional Param "timestamps" - If true, add an RFC3339 or RFC3339Nano timestamp at the beginning of every line of log output. Defaults to false. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> Timestamps -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> Timestamps -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodLog TailLines Source # | Optional Param "tailLines" - If set, the number of lines from the end of the logs to show. If not specified, logs are shown from the creation of the container or sinceSeconds or sinceTime |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> TailLines -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> TailLines -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodLog SinceSeconds Source # | Optional Param "sinceSeconds" - A relative time in seconds before the current time from which to show logs. If this value precedes the time a pod was started, only logs since the pod start will be returned. If this value is in the future, no logs will be returned. Only one of sinceSeconds or sinceTime may be specified. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> SinceSeconds -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> SinceSeconds -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodLog Previous Source # | Optional Param "previous" - Return previous terminated container logs. Defaults to false. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> Previous -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> Previous -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodLog Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodLog LimitBytes Source # | Optional Param "limitBytes" - If set, the number of bytes to read from the server before terminating the log output. This may not display a complete final line of logging, and may return slightly more or slightly less than the specified limit. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> LimitBytes -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> LimitBytes -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodLog Follow Source # | Optional Param "follow" - Follow the log stream of the pod. Defaults to false. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> Follow -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> Follow -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # | |
HasOptionalParam ReadNamespacedPodLog Container Source # | Optional Param "container" - The container for which to stream logs. Defaults to only container if there is one container in the pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> Container -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPodLog contentType res accept -> Container -> KubernetesRequest ReadNamespacedPodLog contentType res accept Source # | |
HasOptionalParam ReadNamespacedPod Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPod contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPod contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPod contentType res accept Source # | |
HasOptionalParam ReadNamespacedPod Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPod contentType res accept -> Export -> KubernetesRequest ReadNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPod contentType res accept -> Export -> KubernetesRequest ReadNamespacedPod contentType res accept Source # | |
HasOptionalParam ReadNamespacedPod Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPod contentType res accept -> Exact -> KubernetesRequest ReadNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPod contentType res accept -> Exact -> KubernetesRequest ReadNamespacedPod contentType res accept Source # | |
HasOptionalParam ReadNamespacedPersistentVolumeClaimStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPersistentVolumeClaimStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPersistentVolumeClaimStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPersistentVolumeClaimStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPersistentVolumeClaimStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedPersistentVolumeClaim Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ReadNamespacedPersistentVolumeClaim Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPersistentVolumeClaim contentType res accept -> Export -> KubernetesRequest ReadNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPersistentVolumeClaim contentType res accept -> Export -> KubernetesRequest ReadNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ReadNamespacedPersistentVolumeClaim Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedPersistentVolumeClaim contentType res accept -> Exact -> KubernetesRequest ReadNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedPersistentVolumeClaim contentType res accept -> Exact -> KubernetesRequest ReadNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ReadNamespacedLimitRange Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ReadNamespacedLimitRange Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedLimitRange contentType res accept -> Export -> KubernetesRequest ReadNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedLimitRange contentType res accept -> Export -> KubernetesRequest ReadNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ReadNamespacedLimitRange Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedLimitRange contentType res accept -> Exact -> KubernetesRequest ReadNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedLimitRange contentType res accept -> Exact -> KubernetesRequest ReadNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ReadNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedEvent contentType res accept Source # | |
HasOptionalParam ReadNamespacedEvent Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedEvent contentType res accept -> Export -> KubernetesRequest ReadNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedEvent contentType res accept -> Export -> KubernetesRequest ReadNamespacedEvent contentType res accept Source # | |
HasOptionalParam ReadNamespacedEvent Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedEvent contentType res accept -> Exact -> KubernetesRequest ReadNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedEvent contentType res accept -> Exact -> KubernetesRequest ReadNamespacedEvent contentType res accept Source # | |
HasOptionalParam ReadNamespacedEndpoints Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ReadNamespacedEndpoints Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedEndpoints contentType res accept -> Export -> KubernetesRequest ReadNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedEndpoints contentType res accept -> Export -> KubernetesRequest ReadNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ReadNamespacedEndpoints Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedEndpoints contentType res accept -> Exact -> KubernetesRequest ReadNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedEndpoints contentType res accept -> Exact -> KubernetesRequest ReadNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ReadNamespacedConfigMap Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ReadNamespacedConfigMap Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedConfigMap contentType res accept -> Export -> KubernetesRequest ReadNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedConfigMap contentType res accept -> Export -> KubernetesRequest ReadNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ReadNamespacedConfigMap Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedConfigMap contentType res accept -> Exact -> KubernetesRequest ReadNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedConfigMap contentType res accept -> Exact -> KubernetesRequest ReadNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ReadNamespaceStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespaceStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespaceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespaceStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespaceStatus contentType res accept Source # | |
HasOptionalParam ReadNamespace Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespace contentType res accept -> Pretty -> KubernetesRequest ReadNamespace contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespace contentType res accept -> Pretty -> KubernetesRequest ReadNamespace contentType res accept Source # | |
HasOptionalParam ReadNamespace Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespace contentType res accept -> Export -> KubernetesRequest ReadNamespace contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespace contentType res accept -> Export -> KubernetesRequest ReadNamespace contentType res accept Source # | |
HasOptionalParam ReadNamespace Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespace contentType res accept -> Exact -> KubernetesRequest ReadNamespace contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespace contentType res accept -> Exact -> KubernetesRequest ReadNamespace contentType res accept Source # | |
HasOptionalParam ReadComponentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ReadComponentStatus contentType res accept -> Pretty -> KubernetesRequest ReadComponentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadComponentStatus contentType res accept -> Pretty -> KubernetesRequest ReadComponentStatus contentType res accept Source # | |
HasOptionalParam PatchPersistentVolumeStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchPersistentVolumeStatus contentType res accept -> Pretty -> KubernetesRequest PatchPersistentVolumeStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchPersistentVolumeStatus contentType res accept -> Pretty -> KubernetesRequest PatchPersistentVolumeStatus contentType res accept Source # | |
HasOptionalParam PatchPersistentVolumeStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchPersistentVolumeStatus contentType res accept -> Force -> KubernetesRequest PatchPersistentVolumeStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchPersistentVolumeStatus contentType res accept -> Force -> KubernetesRequest PatchPersistentVolumeStatus contentType res accept Source # | |
HasOptionalParam PatchPersistentVolumeStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchPersistentVolumeStatus contentType res accept -> FieldManager -> KubernetesRequest PatchPersistentVolumeStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchPersistentVolumeStatus contentType res accept -> FieldManager -> KubernetesRequest PatchPersistentVolumeStatus contentType res accept Source # | |
HasOptionalParam PatchPersistentVolumeStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchPersistentVolumeStatus contentType res accept -> DryRun -> KubernetesRequest PatchPersistentVolumeStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchPersistentVolumeStatus contentType res accept -> DryRun -> KubernetesRequest PatchPersistentVolumeStatus contentType res accept Source # | |
HasOptionalParam PatchPersistentVolume Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchPersistentVolume contentType res accept -> Pretty -> KubernetesRequest PatchPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest PatchPersistentVolume contentType res accept -> Pretty -> KubernetesRequest PatchPersistentVolume contentType res accept Source # | |
HasOptionalParam PatchPersistentVolume Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchPersistentVolume contentType res accept -> Force -> KubernetesRequest PatchPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest PatchPersistentVolume contentType res accept -> Force -> KubernetesRequest PatchPersistentVolume contentType res accept Source # | |
HasOptionalParam PatchPersistentVolume FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchPersistentVolume contentType res accept -> FieldManager -> KubernetesRequest PatchPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest PatchPersistentVolume contentType res accept -> FieldManager -> KubernetesRequest PatchPersistentVolume contentType res accept Source # | |
HasOptionalParam PatchPersistentVolume DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchPersistentVolume contentType res accept -> DryRun -> KubernetesRequest PatchPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest PatchPersistentVolume contentType res accept -> DryRun -> KubernetesRequest PatchPersistentVolume contentType res accept Source # | |
HasOptionalParam PatchNodeStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNodeStatus contentType res accept -> Pretty -> KubernetesRequest PatchNodeStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNodeStatus contentType res accept -> Pretty -> KubernetesRequest PatchNodeStatus contentType res accept Source # | |
HasOptionalParam PatchNodeStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNodeStatus contentType res accept -> Force -> KubernetesRequest PatchNodeStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNodeStatus contentType res accept -> Force -> KubernetesRequest PatchNodeStatus contentType res accept Source # | |
HasOptionalParam PatchNodeStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNodeStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNodeStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNodeStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNodeStatus contentType res accept Source # | |
HasOptionalParam PatchNodeStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNodeStatus contentType res accept -> DryRun -> KubernetesRequest PatchNodeStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNodeStatus contentType res accept -> DryRun -> KubernetesRequest PatchNodeStatus contentType res accept Source # | |
HasOptionalParam PatchNode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNode contentType res accept -> Pretty -> KubernetesRequest PatchNode contentType res accept Source # (-&-) :: KubernetesRequest PatchNode contentType res accept -> Pretty -> KubernetesRequest PatchNode contentType res accept Source # | |
HasOptionalParam PatchNode Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNode contentType res accept -> Force -> KubernetesRequest PatchNode contentType res accept Source # (-&-) :: KubernetesRequest PatchNode contentType res accept -> Force -> KubernetesRequest PatchNode contentType res accept Source # | |
HasOptionalParam PatchNode FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNode contentType res accept -> FieldManager -> KubernetesRequest PatchNode contentType res accept Source # (-&-) :: KubernetesRequest PatchNode contentType res accept -> FieldManager -> KubernetesRequest PatchNode contentType res accept Source # | |
HasOptionalParam PatchNode DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNode contentType res accept -> DryRun -> KubernetesRequest PatchNode contentType res accept Source # (-&-) :: KubernetesRequest PatchNode contentType res accept -> DryRun -> KubernetesRequest PatchNode contentType res accept Source # | |
HasOptionalParam PatchNamespacedServiceStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedServiceStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedServiceStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedServiceStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedServiceStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedServiceStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedServiceStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedServiceStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedServiceStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedServiceStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedServiceStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedServiceStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedServiceStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedServiceStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedServiceStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedServiceStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedServiceAccount Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam PatchNamespacedServiceAccount Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedServiceAccount contentType res accept -> Force -> KubernetesRequest PatchNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedServiceAccount contentType res accept -> Force -> KubernetesRequest PatchNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam PatchNamespacedServiceAccount FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedServiceAccount contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedServiceAccount contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam PatchNamespacedServiceAccount DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedServiceAccount contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedServiceAccount contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam PatchNamespacedService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedService contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedService contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedService contentType res accept Source # | |
HasOptionalParam PatchNamespacedService Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedService contentType res accept -> Force -> KubernetesRequest PatchNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedService contentType res accept -> Force -> KubernetesRequest PatchNamespacedService contentType res accept Source # | |
HasOptionalParam PatchNamespacedService FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedService contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedService contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedService contentType res accept Source # | |
HasOptionalParam PatchNamespacedService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedService contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedService contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedService contentType res accept Source # | |
HasOptionalParam PatchNamespacedSecret Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedSecret contentType res accept Source # | |
HasOptionalParam PatchNamespacedSecret Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedSecret contentType res accept -> Force -> KubernetesRequest PatchNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedSecret contentType res accept -> Force -> KubernetesRequest PatchNamespacedSecret contentType res accept Source # | |
HasOptionalParam PatchNamespacedSecret FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedSecret contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedSecret contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedSecret contentType res accept Source # | |
HasOptionalParam PatchNamespacedSecret DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedSecret contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedSecret contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedSecret contentType res accept Source # | |
HasOptionalParam PatchNamespacedResourceQuotaStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedResourceQuotaStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedResourceQuotaStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedResourceQuotaStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedResourceQuotaStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedResourceQuota Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam PatchNamespacedResourceQuota Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedResourceQuota contentType res accept -> Force -> KubernetesRequest PatchNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedResourceQuota contentType res accept -> Force -> KubernetesRequest PatchNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam PatchNamespacedResourceQuota FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedResourceQuota contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedResourceQuota contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam PatchNamespacedResourceQuota DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedResourceQuota contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedResourceQuota contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationControllerStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationControllerStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationControllerStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationControllerStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicationControllerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationControllerScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationControllerScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationControllerScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationControllerScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicationControllerScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationController Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationController Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationController contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationController contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationController FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationController contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationController contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicationController DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicationController contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicationController contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodTemplate Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodTemplate Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodTemplate contentType res accept -> Force -> KubernetesRequest PatchNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodTemplate contentType res accept -> Force -> KubernetesRequest PatchNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodTemplate FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodTemplate contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodTemplate contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodTemplate DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodTemplate contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodTemplate contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPodStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPodStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedPodStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedPodStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPodStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPodStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedPodStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPodStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPodStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPodStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPodStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedPod Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPod contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPod contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPod contentType res accept Source # | |
HasOptionalParam PatchNamespacedPod Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPod contentType res accept -> Force -> KubernetesRequest PatchNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPod contentType res accept -> Force -> KubernetesRequest PatchNamespacedPod contentType res accept Source # | |
HasOptionalParam PatchNamespacedPod FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPod contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPod contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPod contentType res accept Source # | |
HasOptionalParam PatchNamespacedPod DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPod contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPod contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPod contentType res accept Source # | |
HasOptionalParam PatchNamespacedPersistentVolumeClaimStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedPersistentVolumeClaimStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedPersistentVolumeClaimStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedPersistentVolumeClaimStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPersistentVolumeClaimStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedPersistentVolumeClaim Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam PatchNamespacedPersistentVolumeClaim Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept -> Force -> KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept -> Force -> KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam PatchNamespacedPersistentVolumeClaim FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam PatchNamespacedPersistentVolumeClaim DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam PatchNamespacedLimitRange Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam PatchNamespacedLimitRange Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedLimitRange contentType res accept -> Force -> KubernetesRequest PatchNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedLimitRange contentType res accept -> Force -> KubernetesRequest PatchNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam PatchNamespacedLimitRange FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedLimitRange contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedLimitRange contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam PatchNamespacedLimitRange DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedLimitRange contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedLimitRange contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam PatchNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # | |
HasOptionalParam PatchNamespacedEvent Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEvent contentType res accept -> Force -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEvent contentType res accept -> Force -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # | |
HasOptionalParam PatchNamespacedEvent FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEvent contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEvent contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # | |
HasOptionalParam PatchNamespacedEvent DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedEvent contentType res accept Source # | |
HasOptionalParam PatchNamespacedEndpoints Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam PatchNamespacedEndpoints Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEndpoints contentType res accept -> Force -> KubernetesRequest PatchNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEndpoints contentType res accept -> Force -> KubernetesRequest PatchNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam PatchNamespacedEndpoints FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEndpoints contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEndpoints contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam PatchNamespacedEndpoints DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedEndpoints contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedEndpoints contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam PatchNamespacedConfigMap Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam PatchNamespacedConfigMap Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedConfigMap contentType res accept -> Force -> KubernetesRequest PatchNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedConfigMap contentType res accept -> Force -> KubernetesRequest PatchNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam PatchNamespacedConfigMap FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedConfigMap contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedConfigMap contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam PatchNamespacedConfigMap DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedConfigMap contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedConfigMap contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam PatchNamespaceStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespaceStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespaceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespaceStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespaceStatus contentType res accept Source # | |
HasOptionalParam PatchNamespaceStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespaceStatus contentType res accept -> Force -> KubernetesRequest PatchNamespaceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespaceStatus contentType res accept -> Force -> KubernetesRequest PatchNamespaceStatus contentType res accept Source # | |
HasOptionalParam PatchNamespaceStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespaceStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespaceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespaceStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespaceStatus contentType res accept Source # | |
HasOptionalParam PatchNamespaceStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespaceStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespaceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespaceStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespaceStatus contentType res accept Source # | |
HasOptionalParam PatchNamespace Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespace contentType res accept -> Pretty -> KubernetesRequest PatchNamespace contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespace contentType res accept -> Pretty -> KubernetesRequest PatchNamespace contentType res accept Source # | |
HasOptionalParam PatchNamespace Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespace contentType res accept -> Force -> KubernetesRequest PatchNamespace contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespace contentType res accept -> Force -> KubernetesRequest PatchNamespace contentType res accept Source # | |
HasOptionalParam PatchNamespace FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespace contentType res accept -> FieldManager -> KubernetesRequest PatchNamespace contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespace contentType res accept -> FieldManager -> KubernetesRequest PatchNamespace contentType res accept Source # | |
HasOptionalParam PatchNamespace DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespace contentType res accept -> DryRun -> KubernetesRequest PatchNamespace contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespace contentType res accept -> DryRun -> KubernetesRequest PatchNamespace contentType res accept Source # | |
HasOptionalParam ListServiceForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListServiceForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceAccountForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceAccountForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceAccountForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceAccountForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceAccountForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceAccountForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceAccountForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceAccountForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListServiceAccountForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListServiceAccountForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListSecretForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListSecretForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListSecretForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListSecretForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListSecretForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListSecretForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListSecretForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListSecretForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListSecretForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListSecretForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListSecretForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListResourceQuotaForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListResourceQuotaForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListResourceQuotaForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListResourceQuotaForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListResourceQuotaForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListResourceQuotaForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListResourceQuotaForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListResourceQuotaForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListResourceQuotaForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListResourceQuotaForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicationControllerForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicationControllerForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicationControllerForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicationControllerForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicationControllerForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicationControllerForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicationControllerForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicationControllerForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicationControllerForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListReplicationControllerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodTemplateForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodTemplateForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodTemplateForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodTemplateForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodTemplateForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodTemplateForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodTemplateForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodTemplateForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodTemplateForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPodTemplateForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPodForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPodForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPodForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPersistentVolumeClaimForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPersistentVolumeClaimForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPersistentVolumeClaimForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPersistentVolumeClaimForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPersistentVolumeClaimForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPersistentVolumeClaimForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPersistentVolumeClaimForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPersistentVolumeClaimForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPersistentVolumeClaimForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPersistentVolumeClaimForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListPersistentVolume Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolume contentType res accept -> Watch -> KubernetesRequest ListPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolume contentType res accept -> Watch -> KubernetesRequest ListPersistentVolume contentType res accept Source # | |
HasOptionalParam ListPersistentVolume TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolume contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolume contentType res accept -> TimeoutSeconds -> KubernetesRequest ListPersistentVolume contentType res accept Source # | |
HasOptionalParam ListPersistentVolume ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolume contentType res accept -> ResourceVersion -> KubernetesRequest ListPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolume contentType res accept -> ResourceVersion -> KubernetesRequest ListPersistentVolume contentType res accept Source # | |
HasOptionalParam ListPersistentVolume Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolume contentType res accept -> Pretty -> KubernetesRequest ListPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolume contentType res accept -> Pretty -> KubernetesRequest ListPersistentVolume contentType res accept Source # | |
HasOptionalParam ListPersistentVolume Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolume contentType res accept -> Limit -> KubernetesRequest ListPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolume contentType res accept -> Limit -> KubernetesRequest ListPersistentVolume contentType res accept Source # | |
HasOptionalParam ListPersistentVolume LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolume contentType res accept -> LabelSelector -> KubernetesRequest ListPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolume contentType res accept -> LabelSelector -> KubernetesRequest ListPersistentVolume contentType res accept Source # | |
HasOptionalParam ListPersistentVolume FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolume contentType res accept -> FieldSelector -> KubernetesRequest ListPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolume contentType res accept -> FieldSelector -> KubernetesRequest ListPersistentVolume contentType res accept Source # | |
HasOptionalParam ListPersistentVolume Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolume contentType res accept -> Continue -> KubernetesRequest ListPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolume contentType res accept -> Continue -> KubernetesRequest ListPersistentVolume contentType res accept Source # | |
HasOptionalParam ListPersistentVolume AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListPersistentVolume contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest ListPersistentVolume contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListPersistentVolume contentType res accept Source # | |
HasOptionalParam ListNode Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNode contentType res accept -> Watch -> KubernetesRequest ListNode contentType res accept Source # (-&-) :: KubernetesRequest ListNode contentType res accept -> Watch -> KubernetesRequest ListNode contentType res accept Source # | |
HasOptionalParam ListNode TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNode contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNode contentType res accept Source # (-&-) :: KubernetesRequest ListNode contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNode contentType res accept Source # | |
HasOptionalParam ListNode ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNode contentType res accept -> ResourceVersion -> KubernetesRequest ListNode contentType res accept Source # (-&-) :: KubernetesRequest ListNode contentType res accept -> ResourceVersion -> KubernetesRequest ListNode contentType res accept Source # | |
HasOptionalParam ListNode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNode contentType res accept -> Pretty -> KubernetesRequest ListNode contentType res accept Source # (-&-) :: KubernetesRequest ListNode contentType res accept -> Pretty -> KubernetesRequest ListNode contentType res accept Source # | |
HasOptionalParam ListNode Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNode contentType res accept -> Limit -> KubernetesRequest ListNode contentType res accept Source # (-&-) :: KubernetesRequest ListNode contentType res accept -> Limit -> KubernetesRequest ListNode contentType res accept Source # | |
HasOptionalParam ListNode LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNode contentType res accept -> LabelSelector -> KubernetesRequest ListNode contentType res accept Source # (-&-) :: KubernetesRequest ListNode contentType res accept -> LabelSelector -> KubernetesRequest ListNode contentType res accept Source # | |
HasOptionalParam ListNode FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNode contentType res accept -> FieldSelector -> KubernetesRequest ListNode contentType res accept Source # (-&-) :: KubernetesRequest ListNode contentType res accept -> FieldSelector -> KubernetesRequest ListNode contentType res accept Source # | |
HasOptionalParam ListNode Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNode contentType res accept -> Continue -> KubernetesRequest ListNode contentType res accept Source # (-&-) :: KubernetesRequest ListNode contentType res accept -> Continue -> KubernetesRequest ListNode contentType res accept Source # | |
HasOptionalParam ListNode AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNode contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNode contentType res accept Source # (-&-) :: KubernetesRequest ListNode contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNode contentType res accept Source # | |
HasOptionalParam ListNamespacedServiceAccount Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> Watch -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> Watch -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ListNamespacedServiceAccount TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ListNamespacedServiceAccount ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ListNamespacedServiceAccount Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ListNamespacedServiceAccount Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> Limit -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> Limit -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ListNamespacedServiceAccount LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ListNamespacedServiceAccount FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ListNamespacedServiceAccount Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> Continue -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> Continue -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ListNamespacedServiceAccount AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedServiceAccount contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam ListNamespacedService Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedService contentType res accept -> Watch -> KubernetesRequest ListNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedService contentType res accept -> Watch -> KubernetesRequest ListNamespacedService contentType res accept Source # | |
HasOptionalParam ListNamespacedService TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedService contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedService contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedService contentType res accept Source # | |
HasOptionalParam ListNamespacedService ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedService contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedService contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedService contentType res accept Source # | |
HasOptionalParam ListNamespacedService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedService contentType res accept -> Pretty -> KubernetesRequest ListNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedService contentType res accept -> Pretty -> KubernetesRequest ListNamespacedService contentType res accept Source # | |
HasOptionalParam ListNamespacedService Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedService contentType res accept -> Limit -> KubernetesRequest ListNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedService contentType res accept -> Limit -> KubernetesRequest ListNamespacedService contentType res accept Source # | |
HasOptionalParam ListNamespacedService LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedService contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedService contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedService contentType res accept Source # | |
HasOptionalParam ListNamespacedService FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedService contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedService contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedService contentType res accept Source # | |
HasOptionalParam ListNamespacedService Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedService contentType res accept -> Continue -> KubernetesRequest ListNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedService contentType res accept -> Continue -> KubernetesRequest ListNamespacedService contentType res accept Source # | |
HasOptionalParam ListNamespacedService AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedService contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedService contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedService contentType res accept Source # | |
HasOptionalParam ListNamespacedSecret Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedSecret contentType res accept -> Watch -> KubernetesRequest ListNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedSecret contentType res accept -> Watch -> KubernetesRequest ListNamespacedSecret contentType res accept Source # | |
HasOptionalParam ListNamespacedSecret TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedSecret contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedSecret contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedSecret contentType res accept Source # | |
HasOptionalParam ListNamespacedSecret ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedSecret contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedSecret contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedSecret contentType res accept Source # | |
HasOptionalParam ListNamespacedSecret Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest ListNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest ListNamespacedSecret contentType res accept Source # | |
HasOptionalParam ListNamespacedSecret Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedSecret contentType res accept -> Limit -> KubernetesRequest ListNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedSecret contentType res accept -> Limit -> KubernetesRequest ListNamespacedSecret contentType res accept Source # | |
HasOptionalParam ListNamespacedSecret LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedSecret contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedSecret contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedSecret contentType res accept Source # | |
HasOptionalParam ListNamespacedSecret FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedSecret contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedSecret contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedSecret contentType res accept Source # | |
HasOptionalParam ListNamespacedSecret Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedSecret contentType res accept -> Continue -> KubernetesRequest ListNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedSecret contentType res accept -> Continue -> KubernetesRequest ListNamespacedSecret contentType res accept Source # | |
HasOptionalParam ListNamespacedSecret AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedSecret contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedSecret contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedSecret contentType res accept Source # | |
HasOptionalParam ListNamespacedResourceQuota Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> Watch -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> Watch -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ListNamespacedResourceQuota TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ListNamespacedResourceQuota ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ListNamespacedResourceQuota Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ListNamespacedResourceQuota Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> Limit -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> Limit -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ListNamespacedResourceQuota LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ListNamespacedResourceQuota FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ListNamespacedResourceQuota Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> Continue -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> Continue -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ListNamespacedResourceQuota AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedResourceQuota contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicationController Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> Watch -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> Watch -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicationController TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicationController ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicationController Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicationController Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> Limit -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> Limit -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicationController LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicationController FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicationController Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> Continue -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> Continue -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicationController AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicationController contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam ListNamespacedPodTemplate Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> Watch -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> Watch -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ListNamespacedPodTemplate TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ListNamespacedPodTemplate ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ListNamespacedPodTemplate Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ListNamespacedPodTemplate Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> Limit -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> Limit -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ListNamespacedPodTemplate LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ListNamespacedPodTemplate FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ListNamespacedPodTemplate Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> Continue -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> Continue -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ListNamespacedPodTemplate AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPodTemplate contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam ListNamespacedPod Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPod contentType res accept -> Watch -> KubernetesRequest ListNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPod contentType res accept -> Watch -> KubernetesRequest ListNamespacedPod contentType res accept Source # | |
HasOptionalParam ListNamespacedPod TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPod contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPod contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedPod contentType res accept Source # | |
HasOptionalParam ListNamespacedPod ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPod contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPod contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedPod contentType res accept Source # | |
HasOptionalParam ListNamespacedPod Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPod contentType res accept -> Pretty -> KubernetesRequest ListNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPod contentType res accept -> Pretty -> KubernetesRequest ListNamespacedPod contentType res accept Source # | |
HasOptionalParam ListNamespacedPod Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPod contentType res accept -> Limit -> KubernetesRequest ListNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPod contentType res accept -> Limit -> KubernetesRequest ListNamespacedPod contentType res accept Source # | |
HasOptionalParam ListNamespacedPod LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPod contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPod contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedPod contentType res accept Source # | |
HasOptionalParam ListNamespacedPod FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPod contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPod contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedPod contentType res accept Source # | |
HasOptionalParam ListNamespacedPod Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPod contentType res accept -> Continue -> KubernetesRequest ListNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPod contentType res accept -> Continue -> KubernetesRequest ListNamespacedPod contentType res accept Source # | |
HasOptionalParam ListNamespacedPod AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPod contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPod contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedPod contentType res accept Source # | |
HasOptionalParam ListNamespacedPersistentVolumeClaim Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> Watch -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> Watch -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ListNamespacedPersistentVolumeClaim TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ListNamespacedPersistentVolumeClaim ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ListNamespacedPersistentVolumeClaim Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ListNamespacedPersistentVolumeClaim Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> Limit -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> Limit -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ListNamespacedPersistentVolumeClaim LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ListNamespacedPersistentVolumeClaim FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ListNamespacedPersistentVolumeClaim Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> Continue -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> Continue -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ListNamespacedPersistentVolumeClaim AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam ListNamespacedLimitRange Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> Watch -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> Watch -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ListNamespacedLimitRange TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ListNamespacedLimitRange ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ListNamespacedLimitRange Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ListNamespacedLimitRange Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> Limit -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> Limit -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ListNamespacedLimitRange LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ListNamespacedLimitRange FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ListNamespacedLimitRange Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> Continue -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> Continue -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ListNamespacedLimitRange AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLimitRange contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> Watch -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> Watch -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> Limit -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> Limit -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> Continue -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> Continue -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEvent AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEvent contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEvent contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedEvent contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpoints Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> Watch -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> Watch -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpoints TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpoints ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpoints Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpoints Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> Limit -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> Limit -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpoints LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpoints FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpoints Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> Continue -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> Continue -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ListNamespacedEndpoints AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedEndpoints contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam ListNamespacedConfigMap Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> Watch -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> Watch -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ListNamespacedConfigMap TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ListNamespacedConfigMap ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ListNamespacedConfigMap Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ListNamespacedConfigMap Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> Limit -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> Limit -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ListNamespacedConfigMap LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ListNamespacedConfigMap FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ListNamespacedConfigMap Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> Continue -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> Continue -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ListNamespacedConfigMap AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedConfigMap contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam ListNamespace Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespace contentType res accept -> Watch -> KubernetesRequest ListNamespace contentType res accept Source # (-&-) :: KubernetesRequest ListNamespace contentType res accept -> Watch -> KubernetesRequest ListNamespace contentType res accept Source # | |
HasOptionalParam ListNamespace TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespace contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespace contentType res accept Source # (-&-) :: KubernetesRequest ListNamespace contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespace contentType res accept Source # | |
HasOptionalParam ListNamespace ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespace contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespace contentType res accept Source # (-&-) :: KubernetesRequest ListNamespace contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespace contentType res accept Source # | |
HasOptionalParam ListNamespace Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespace contentType res accept -> Pretty -> KubernetesRequest ListNamespace contentType res accept Source # (-&-) :: KubernetesRequest ListNamespace contentType res accept -> Pretty -> KubernetesRequest ListNamespace contentType res accept Source # | |
HasOptionalParam ListNamespace Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespace contentType res accept -> Limit -> KubernetesRequest ListNamespace contentType res accept Source # (-&-) :: KubernetesRequest ListNamespace contentType res accept -> Limit -> KubernetesRequest ListNamespace contentType res accept Source # | |
HasOptionalParam ListNamespace LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespace contentType res accept -> LabelSelector -> KubernetesRequest ListNamespace contentType res accept Source # (-&-) :: KubernetesRequest ListNamespace contentType res accept -> LabelSelector -> KubernetesRequest ListNamespace contentType res accept Source # | |
HasOptionalParam ListNamespace FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespace contentType res accept -> FieldSelector -> KubernetesRequest ListNamespace contentType res accept Source # (-&-) :: KubernetesRequest ListNamespace contentType res accept -> FieldSelector -> KubernetesRequest ListNamespace contentType res accept Source # | |
HasOptionalParam ListNamespace Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespace contentType res accept -> Continue -> KubernetesRequest ListNamespace contentType res accept Source # (-&-) :: KubernetesRequest ListNamespace contentType res accept -> Continue -> KubernetesRequest ListNamespace contentType res accept Source # | |
HasOptionalParam ListNamespace AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListNamespace contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespace contentType res accept Source # (-&-) :: KubernetesRequest ListNamespace contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespace contentType res accept Source # | |
HasOptionalParam ListLimitRangeForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLimitRangeForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLimitRangeForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLimitRangeForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLimitRangeForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLimitRangeForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLimitRangeForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLimitRangeForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLimitRangeForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListLimitRangeForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEventForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEventForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListEventForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointsForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointsForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointsForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointsForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointsForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointsForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointsForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointsForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListEndpointsForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListEndpointsForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListEndpointsForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListConfigMapForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListConfigMapForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListConfigMapForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListConfigMapForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListConfigMapForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListConfigMapForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListConfigMapForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListConfigMapForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListConfigMapForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListConfigMapForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListConfigMapForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListComponentStatus Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListComponentStatus contentType res accept -> Watch -> KubernetesRequest ListComponentStatus contentType res accept Source # (-&-) :: KubernetesRequest ListComponentStatus contentType res accept -> Watch -> KubernetesRequest ListComponentStatus contentType res accept Source # | |
HasOptionalParam ListComponentStatus TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListComponentStatus contentType res accept -> TimeoutSeconds -> KubernetesRequest ListComponentStatus contentType res accept Source # (-&-) :: KubernetesRequest ListComponentStatus contentType res accept -> TimeoutSeconds -> KubernetesRequest ListComponentStatus contentType res accept Source # | |
HasOptionalParam ListComponentStatus ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListComponentStatus contentType res accept -> ResourceVersion -> KubernetesRequest ListComponentStatus contentType res accept Source # (-&-) :: KubernetesRequest ListComponentStatus contentType res accept -> ResourceVersion -> KubernetesRequest ListComponentStatus contentType res accept Source # | |
HasOptionalParam ListComponentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListComponentStatus contentType res accept -> Pretty -> KubernetesRequest ListComponentStatus contentType res accept Source # (-&-) :: KubernetesRequest ListComponentStatus contentType res accept -> Pretty -> KubernetesRequest ListComponentStatus contentType res accept Source # | |
HasOptionalParam ListComponentStatus Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListComponentStatus contentType res accept -> Limit -> KubernetesRequest ListComponentStatus contentType res accept Source # (-&-) :: KubernetesRequest ListComponentStatus contentType res accept -> Limit -> KubernetesRequest ListComponentStatus contentType res accept Source # | |
HasOptionalParam ListComponentStatus LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListComponentStatus contentType res accept -> LabelSelector -> KubernetesRequest ListComponentStatus contentType res accept Source # (-&-) :: KubernetesRequest ListComponentStatus contentType res accept -> LabelSelector -> KubernetesRequest ListComponentStatus contentType res accept Source # | |
HasOptionalParam ListComponentStatus FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListComponentStatus contentType res accept -> FieldSelector -> KubernetesRequest ListComponentStatus contentType res accept Source # (-&-) :: KubernetesRequest ListComponentStatus contentType res accept -> FieldSelector -> KubernetesRequest ListComponentStatus contentType res accept Source # | |
HasOptionalParam ListComponentStatus Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListComponentStatus contentType res accept -> Continue -> KubernetesRequest ListComponentStatus contentType res accept Source # (-&-) :: KubernetesRequest ListComponentStatus contentType res accept -> Continue -> KubernetesRequest ListComponentStatus contentType res accept Source # | |
HasOptionalParam ListComponentStatus AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ListComponentStatus contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListComponentStatus contentType res accept Source # (-&-) :: KubernetesRequest ListComponentStatus contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListComponentStatus contentType res accept Source # | |
HasOptionalParam DeletePersistentVolume PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeletePersistentVolume contentType res accept -> PropagationPolicy -> KubernetesRequest DeletePersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeletePersistentVolume contentType res accept -> PropagationPolicy -> KubernetesRequest DeletePersistentVolume contentType res accept Source # | |
HasOptionalParam DeletePersistentVolume Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeletePersistentVolume contentType res accept -> Pretty -> KubernetesRequest DeletePersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeletePersistentVolume contentType res accept -> Pretty -> KubernetesRequest DeletePersistentVolume contentType res accept Source # | |
HasOptionalParam DeletePersistentVolume OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeletePersistentVolume contentType res accept -> OrphanDependents -> KubernetesRequest DeletePersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeletePersistentVolume contentType res accept -> OrphanDependents -> KubernetesRequest DeletePersistentVolume contentType res accept Source # | |
HasOptionalParam DeletePersistentVolume GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeletePersistentVolume contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeletePersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeletePersistentVolume contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeletePersistentVolume contentType res accept Source # | |
HasOptionalParam DeletePersistentVolume DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeletePersistentVolume contentType res accept -> DryRun -> KubernetesRequest DeletePersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeletePersistentVolume contentType res accept -> DryRun -> KubernetesRequest DeletePersistentVolume contentType res accept Source # | |
HasOptionalParam DeleteNode PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNode contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteNode contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNode contentType res accept Source # | |
HasOptionalParam DeleteNode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNode contentType res accept -> Pretty -> KubernetesRequest DeleteNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteNode contentType res accept -> Pretty -> KubernetesRequest DeleteNode contentType res accept Source # | |
HasOptionalParam DeleteNode OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNode contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteNode contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNode contentType res accept Source # | |
HasOptionalParam DeleteNode GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNode contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteNode contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNode contentType res accept Source # | |
HasOptionalParam DeleteNode DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNode contentType res accept -> DryRun -> KubernetesRequest DeleteNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteNode contentType res accept -> DryRun -> KubernetesRequest DeleteNode contentType res accept Source # | |
HasOptionalParam DeleteNamespacedServiceAccount PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedServiceAccount contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedServiceAccount contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteNamespacedServiceAccount Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteNamespacedServiceAccount OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedServiceAccount contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedServiceAccount contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteNamespacedServiceAccount GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedServiceAccount contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedServiceAccount contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteNamespacedServiceAccount DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedServiceAccount contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedServiceAccount contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteNamespacedService PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedService contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedService contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedService contentType res accept Source # | |
HasOptionalParam DeleteNamespacedService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedService contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedService contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedService contentType res accept Source # | |
HasOptionalParam DeleteNamespacedService OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedService contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedService contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedService contentType res accept Source # | |
HasOptionalParam DeleteNamespacedService GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedService contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedService contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedService contentType res accept Source # | |
HasOptionalParam DeleteNamespacedService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedService contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedService contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedService contentType res accept Source # | |
HasOptionalParam DeleteNamespacedSecret PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedSecret contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedSecret contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteNamespacedSecret Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteNamespacedSecret OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedSecret contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedSecret contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteNamespacedSecret GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedSecret contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedSecret contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteNamespacedSecret DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedSecret contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedSecret contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteNamespacedResourceQuota PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedResourceQuota contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedResourceQuota contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteNamespacedResourceQuota Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteNamespacedResourceQuota OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedResourceQuota contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedResourceQuota contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteNamespacedResourceQuota GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedResourceQuota contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedResourceQuota contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteNamespacedResourceQuota DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedResourceQuota contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedResourceQuota contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicationController PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicationController contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicationController contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicationController Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicationController OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicationController contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicationController contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicationController GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicationController contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicationController contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicationController DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicationController contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicationController contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodTemplate PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodTemplate contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodTemplate contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodTemplate Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodTemplate OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodTemplate contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodTemplate contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodTemplate GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodTemplate contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodTemplate contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPodTemplate DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPodTemplate contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPodTemplate contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPod PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPod contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPod contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPod Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPod contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPod contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPod OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPod contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPod contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPod GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPod contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPod contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPod DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPod contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPod contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPersistentVolumeClaim PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPersistentVolumeClaim Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPersistentVolumeClaim OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPersistentVolumeClaim GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteNamespacedPersistentVolumeClaim DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLimitRange PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLimitRange contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLimitRange contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLimitRange Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLimitRange OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLimitRange contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLimitRange contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLimitRange GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLimitRange contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLimitRange contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLimitRange DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLimitRange contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLimitRange contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEvent PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEvent OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEvent GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEvent DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEndpoints PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEndpoints contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEndpoints contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEndpoints Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEndpoints OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEndpoints contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEndpoints contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEndpoints GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEndpoints contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEndpoints contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteNamespacedEndpoints DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedEndpoints contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedEndpoints contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteNamespacedConfigMap PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedConfigMap contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedConfigMap contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteNamespacedConfigMap Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteNamespacedConfigMap OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedConfigMap contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedConfigMap contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteNamespacedConfigMap GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedConfigMap contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedConfigMap contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteNamespacedConfigMap DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedConfigMap contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedConfigMap contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteNamespace PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespace contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespace contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespace contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespace contentType res accept Source # | |
HasOptionalParam DeleteNamespace Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespace contentType res accept -> Pretty -> KubernetesRequest DeleteNamespace contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespace contentType res accept -> Pretty -> KubernetesRequest DeleteNamespace contentType res accept Source # | |
HasOptionalParam DeleteNamespace OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespace contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespace contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespace contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespace contentType res accept Source # | |
HasOptionalParam DeleteNamespace GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespace contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespace contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespace contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespace contentType res accept Source # | |
HasOptionalParam DeleteNamespace DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespace contentType res accept -> DryRun -> KubernetesRequest DeleteNamespace contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespace contentType res accept -> DryRun -> KubernetesRequest DeleteNamespace contentType res accept Source # | |
HasOptionalParam DeleteCollectionPersistentVolume TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # | |
HasOptionalParam DeleteCollectionPersistentVolume ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # | |
HasOptionalParam DeleteCollectionPersistentVolume PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # | |
HasOptionalParam DeleteCollectionPersistentVolume Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # | |
HasOptionalParam DeleteCollectionPersistentVolume OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # | |
HasOptionalParam DeleteCollectionPersistentVolume Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> Limit -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> Limit -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # | |
HasOptionalParam DeleteCollectionPersistentVolume LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # | |
HasOptionalParam DeleteCollectionPersistentVolume GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # | |
HasOptionalParam DeleteCollectionPersistentVolume FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # | |
HasOptionalParam DeleteCollectionPersistentVolume DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # | |
HasOptionalParam DeleteCollectionPersistentVolume Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> Continue -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionPersistentVolume contentType res accept -> Continue -> KubernetesRequest DeleteCollectionPersistentVolume contentType res accept Source # | |
HasOptionalParam DeleteCollectionNode TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNode contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNode contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNode contentType res accept Source # | |
HasOptionalParam DeleteCollectionNode ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNode contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNode contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNode contentType res accept Source # | |
HasOptionalParam DeleteCollectionNode PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNode contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNode contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNode contentType res accept Source # | |
HasOptionalParam DeleteCollectionNode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNode contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNode contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNode contentType res accept Source # | |
HasOptionalParam DeleteCollectionNode OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNode contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNode contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNode contentType res accept Source # | |
HasOptionalParam DeleteCollectionNode Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNode contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNode contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNode contentType res accept Source # | |
HasOptionalParam DeleteCollectionNode LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNode contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNode contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNode contentType res accept Source # | |
HasOptionalParam DeleteCollectionNode GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNode contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNode contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNode contentType res accept Source # | |
HasOptionalParam DeleteCollectionNode FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNode contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNode contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNode contentType res accept Source # | |
HasOptionalParam DeleteCollectionNode DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNode contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNode contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNode contentType res accept Source # | |
HasOptionalParam DeleteCollectionNode Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNode contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNode contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNode contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNode contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedServiceAccount TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedServiceAccount ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedServiceAccount PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedServiceAccount Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedServiceAccount OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedServiceAccount Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedServiceAccount LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedServiceAccount GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedServiceAccount FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedServiceAccount DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedServiceAccount Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedSecret TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedSecret ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedSecret PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedSecret Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedSecret OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedSecret Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedSecret LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedSecret GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedSecret FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedSecret DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedSecret Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedSecret contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedResourceQuota TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedResourceQuota ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedResourceQuota PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedResourceQuota Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedResourceQuota OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedResourceQuota Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedResourceQuota LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedResourceQuota GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedResourceQuota FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedResourceQuota DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedResourceQuota Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicationController TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicationController ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicationController PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicationController Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicationController OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicationController Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicationController LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicationController GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicationController FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicationController DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicationController Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodTemplate TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodTemplate ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodTemplate PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodTemplate Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodTemplate OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodTemplate Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodTemplate LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodTemplate GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodTemplate FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodTemplate DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPodTemplate Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPod TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPod ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPod PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPod Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPod OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPod Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPod LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPod GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPod FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPod DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPod Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPod contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedPod contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedPersistentVolumeClaim Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLimitRange TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLimitRange ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLimitRange PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLimitRange Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLimitRange OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLimitRange Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLimitRange LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLimitRange GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLimitRange FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLimitRange DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLimitRange Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEvent Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedEvent contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpoints TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpoints ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpoints PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpoints Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpoints OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpoints Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpoints LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpoints GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpoints FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpoints DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedEndpoints Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedConfigMap TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedConfigMap ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedConfigMap PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedConfigMap Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedConfigMap OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedConfigMap Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedConfigMap LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedConfigMap GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedConfigMap FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedConfigMap DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedConfigMap Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam CreatePersistentVolume Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreatePersistentVolume contentType res accept -> Pretty -> KubernetesRequest CreatePersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest CreatePersistentVolume contentType res accept -> Pretty -> KubernetesRequest CreatePersistentVolume contentType res accept Source # | |
HasOptionalParam CreatePersistentVolume FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreatePersistentVolume contentType res accept -> FieldManager -> KubernetesRequest CreatePersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest CreatePersistentVolume contentType res accept -> FieldManager -> KubernetesRequest CreatePersistentVolume contentType res accept Source # | |
HasOptionalParam CreatePersistentVolume DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreatePersistentVolume contentType res accept -> DryRun -> KubernetesRequest CreatePersistentVolume contentType res accept Source # (-&-) :: KubernetesRequest CreatePersistentVolume contentType res accept -> DryRun -> KubernetesRequest CreatePersistentVolume contentType res accept Source # | |
HasOptionalParam CreateNode Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNode contentType res accept -> Pretty -> KubernetesRequest CreateNode contentType res accept Source # (-&-) :: KubernetesRequest CreateNode contentType res accept -> Pretty -> KubernetesRequest CreateNode contentType res accept Source # | |
HasOptionalParam CreateNode FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNode contentType res accept -> FieldManager -> KubernetesRequest CreateNode contentType res accept Source # (-&-) :: KubernetesRequest CreateNode contentType res accept -> FieldManager -> KubernetesRequest CreateNode contentType res accept Source # | |
HasOptionalParam CreateNode DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNode contentType res accept -> DryRun -> KubernetesRequest CreateNode contentType res accept Source # (-&-) :: KubernetesRequest CreateNode contentType res accept -> DryRun -> KubernetesRequest CreateNode contentType res accept Source # | |
HasOptionalParam CreateNamespacedServiceAccountToken Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedServiceAccountToken contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedServiceAccountToken contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedServiceAccountToken contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedServiceAccountToken contentType res accept Source # | |
HasOptionalParam CreateNamespacedServiceAccountToken FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedServiceAccountToken contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedServiceAccountToken contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedServiceAccountToken contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedServiceAccountToken contentType res accept Source # | |
HasOptionalParam CreateNamespacedServiceAccountToken DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedServiceAccountToken contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedServiceAccountToken contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedServiceAccountToken contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedServiceAccountToken contentType res accept Source # | |
HasOptionalParam CreateNamespacedServiceAccount Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedServiceAccount contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam CreateNamespacedServiceAccount FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedServiceAccount contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedServiceAccount contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam CreateNamespacedServiceAccount DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedServiceAccount contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedServiceAccount contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedServiceAccount contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedServiceAccount contentType res accept Source # | |
HasOptionalParam CreateNamespacedService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedService contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedService contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedService contentType res accept Source # | |
HasOptionalParam CreateNamespacedService FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedService contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedService contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedService contentType res accept Source # | |
HasOptionalParam CreateNamespacedService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedService contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedService contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedService contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedService contentType res accept Source # | |
HasOptionalParam CreateNamespacedSecret Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedSecret contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedSecret contentType res accept Source # | |
HasOptionalParam CreateNamespacedSecret FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedSecret contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedSecret contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedSecret contentType res accept Source # | |
HasOptionalParam CreateNamespacedSecret DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedSecret contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedSecret contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedSecret contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedSecret contentType res accept Source # | |
HasOptionalParam CreateNamespacedResourceQuota Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedResourceQuota contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam CreateNamespacedResourceQuota FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedResourceQuota contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedResourceQuota contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam CreateNamespacedResourceQuota DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedResourceQuota contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedResourceQuota contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedResourceQuota contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedResourceQuota contentType res accept Source # | |
HasOptionalParam CreateNamespacedReplicationController Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedReplicationController contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam CreateNamespacedReplicationController FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedReplicationController contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedReplicationController contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam CreateNamespacedReplicationController DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedReplicationController contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedReplicationController contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedReplicationController contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedReplicationController contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodTemplate Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodTemplate contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodTemplate FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodTemplate contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodTemplate contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodTemplate DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodTemplate contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPodTemplate contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodTemplate contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPodTemplate contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodEviction Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodEviction contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPodEviction contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodEviction contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPodEviction contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodEviction FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodEviction contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPodEviction contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodEviction contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPodEviction contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodEviction DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodEviction contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPodEviction contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodEviction contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPodEviction contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodBinding contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPodBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodBinding contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPodBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodBinding contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPodBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodBinding contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPodBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedPodBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPodBinding contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPodBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPodBinding contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPodBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedPod Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPod contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPod contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPod contentType res accept Source # | |
HasOptionalParam CreateNamespacedPod FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPod contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPod contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPod contentType res accept Source # | |
HasOptionalParam CreateNamespacedPod DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPod contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPod contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPod contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPod contentType res accept Source # | |
HasOptionalParam CreateNamespacedPersistentVolumeClaim Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam CreateNamespacedPersistentVolumeClaim FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam CreateNamespacedPersistentVolumeClaim DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedPersistentVolumeClaim contentType res accept Source # | |
HasOptionalParam CreateNamespacedLimitRange Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLimitRange contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam CreateNamespacedLimitRange FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLimitRange contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLimitRange contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam CreateNamespacedLimitRange DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLimitRange contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedLimitRange contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLimitRange contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedLimitRange contentType res accept Source # | |
HasOptionalParam CreateNamespacedEvent Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedEvent contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedEvent contentType res accept Source # | |
HasOptionalParam CreateNamespacedEvent FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedEvent contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedEvent contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedEvent contentType res accept Source # | |
HasOptionalParam CreateNamespacedEvent DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedEvent contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedEvent contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedEvent contentType res accept Source # | |
HasOptionalParam CreateNamespacedEndpoints Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedEndpoints contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam CreateNamespacedEndpoints FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedEndpoints contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedEndpoints contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam CreateNamespacedEndpoints DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedEndpoints contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedEndpoints contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedEndpoints contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedEndpoints contentType res accept Source # | |
HasOptionalParam CreateNamespacedConfigMap Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedConfigMap contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam CreateNamespacedConfigMap FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedConfigMap contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedConfigMap contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam CreateNamespacedConfigMap DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedConfigMap contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedConfigMap contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedConfigMap contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedConfigMap contentType res accept Source # | |
HasOptionalParam CreateNamespacedBinding Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedBinding contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedBinding contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedBinding FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedBinding contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedBinding contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedBinding contentType res accept Source # | |
HasOptionalParam CreateNamespacedBinding DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedBinding contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedBinding contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedBinding contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedBinding contentType res accept Source # | |
HasOptionalParam CreateNamespace Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespace contentType res accept -> Pretty -> KubernetesRequest CreateNamespace contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespace contentType res accept -> Pretty -> KubernetesRequest CreateNamespace contentType res accept Source # | |
HasOptionalParam CreateNamespace FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespace contentType res accept -> FieldManager -> KubernetesRequest CreateNamespace contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespace contentType res accept -> FieldManager -> KubernetesRequest CreateNamespace contentType res accept Source # | |
HasOptionalParam CreateNamespace DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespace contentType res accept -> DryRun -> KubernetesRequest CreateNamespace contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespace contentType res accept -> DryRun -> KubernetesRequest CreateNamespace contentType res accept Source # | |
HasOptionalParam ConnectPutNodeProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPutNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPutNodeProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectPutNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPutNodeProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectPutNodeProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPutNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectPutNodeProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectPutNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectPutNodeProxy contentType res accept Source # | |
HasOptionalParam ConnectPutNamespacedServiceProxyWithPath Path2 Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPutNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPutNamespacedServiceProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectPutNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPutNamespacedServiceProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectPutNamespacedServiceProxy Path Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPutNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectPutNamespacedServiceProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectPutNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectPutNamespacedServiceProxy contentType res accept Source # | |
HasOptionalParam ConnectPutNamespacedPodProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPutNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPutNamespacedPodProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectPutNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPutNamespacedPodProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectPutNamespacedPodProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPutNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectPutNamespacedPodProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectPutNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectPutNamespacedPodProxy contentType res accept Source # | |
HasOptionalParam ConnectPostNodeProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPostNodeProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPostNodeProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectPostNodeProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectPostNodeProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectPostNodeProxy contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedServiceProxyWithPath Path2 Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPostNamespacedServiceProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPostNamespacedServiceProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedServiceProxy Path Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectPostNamespacedServiceProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectPostNamespacedServiceProxy contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPostNamespacedPodProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPostNamespacedPodProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectPostNamespacedPodProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectPostNamespacedPodProxy contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodPortforward Ports Source # | Optional Param "ports" - List of ports to forward Required when using WebSockets |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodPortforward contentType res accept -> Ports -> KubernetesRequest ConnectPostNamespacedPodPortforward contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodPortforward contentType res accept -> Ports -> KubernetesRequest ConnectPostNamespacedPodPortforward contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodExec Tty Source # | Optional Param "tty" - TTY if true indicates that a tty will be allocated for the exec call. Defaults to false. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodExec contentType res accept -> Tty -> KubernetesRequest ConnectPostNamespacedPodExec contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodExec contentType res accept -> Tty -> KubernetesRequest ConnectPostNamespacedPodExec contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodExec Stdout Source # | Optional Param "stdout" - Redirect the standard output stream of the pod for this call. Defaults to true. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodExec contentType res accept -> Stdout -> KubernetesRequest ConnectPostNamespacedPodExec contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodExec contentType res accept -> Stdout -> KubernetesRequest ConnectPostNamespacedPodExec contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodExec Stdin Source # | Optional Param "stdin" - Redirect the standard input stream of the pod for this call. Defaults to false. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodExec contentType res accept -> Stdin -> KubernetesRequest ConnectPostNamespacedPodExec contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodExec contentType res accept -> Stdin -> KubernetesRequest ConnectPostNamespacedPodExec contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodExec Stderr Source # | Optional Param "stderr" - Redirect the standard error stream of the pod for this call. Defaults to true. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodExec contentType res accept -> Stderr -> KubernetesRequest ConnectPostNamespacedPodExec contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodExec contentType res accept -> Stderr -> KubernetesRequest ConnectPostNamespacedPodExec contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodExec Container Source # | Optional Param "container" - Container in which to execute the command. Defaults to only container if there is only one container in the pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodExec contentType res accept -> Container -> KubernetesRequest ConnectPostNamespacedPodExec contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodExec contentType res accept -> Container -> KubernetesRequest ConnectPostNamespacedPodExec contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodExec Command Source # | Optional Param "command" - Command is the remote command to execute. argv array. Not executed within a shell. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodExec contentType res accept -> Command -> KubernetesRequest ConnectPostNamespacedPodExec contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodExec contentType res accept -> Command -> KubernetesRequest ConnectPostNamespacedPodExec contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodAttach Tty Source # | Optional Param "tty" - TTY if true indicates that a tty will be allocated for the attach call. This is passed through the container runtime so the tty is allocated on the worker node by the container runtime. Defaults to false. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept -> Tty -> KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept -> Tty -> KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodAttach Stdout Source # | Optional Param "stdout" - Stdout if true indicates that stdout is to be redirected for the attach call. Defaults to true. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept -> Stdout -> KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept -> Stdout -> KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodAttach Stdin Source # | Optional Param "stdin" - Stdin if true, redirects the standard input stream of the pod for this call. Defaults to false. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept -> Stdin -> KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept -> Stdin -> KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodAttach Stderr Source # | Optional Param "stderr" - Stderr if true indicates that stderr is to be redirected for the attach call. Defaults to true. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept -> Stderr -> KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept -> Stderr -> KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept Source # | |
HasOptionalParam ConnectPostNamespacedPodAttach Container Source # | Optional Param "container" - The container in which to execute the command. Defaults to only container if there is only one container in the pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept -> Container -> KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept Source # (-&-) :: KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept -> Container -> KubernetesRequest ConnectPostNamespacedPodAttach contentType res accept Source # | |
HasOptionalParam ConnectPatchNodeProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPatchNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPatchNodeProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectPatchNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPatchNodeProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectPatchNodeProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPatchNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectPatchNodeProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectPatchNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectPatchNodeProxy contentType res accept Source # | |
HasOptionalParam ConnectPatchNamespacedServiceProxyWithPath Path2 Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPatchNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPatchNamespacedServiceProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectPatchNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPatchNamespacedServiceProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectPatchNamespacedServiceProxy Path Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPatchNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectPatchNamespacedServiceProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectPatchNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectPatchNamespacedServiceProxy contentType res accept Source # | |
HasOptionalParam ConnectPatchNamespacedPodProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPatchNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPatchNamespacedPodProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectPatchNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectPatchNamespacedPodProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectPatchNamespacedPodProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectPatchNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectPatchNamespacedPodProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectPatchNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectPatchNamespacedPodProxy contentType res accept Source # | |
HasOptionalParam ConnectOptionsNodeProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectOptionsNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectOptionsNodeProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectOptionsNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectOptionsNodeProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectOptionsNodeProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectOptionsNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectOptionsNodeProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectOptionsNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectOptionsNodeProxy contentType res accept Source # | |
HasOptionalParam ConnectOptionsNamespacedServiceProxyWithPath Path2 Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectOptionsNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectOptionsNamespacedServiceProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectOptionsNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectOptionsNamespacedServiceProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectOptionsNamespacedServiceProxy Path Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectOptionsNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectOptionsNamespacedServiceProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectOptionsNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectOptionsNamespacedServiceProxy contentType res accept Source # | |
HasOptionalParam ConnectOptionsNamespacedPodProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectOptionsNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectOptionsNamespacedPodProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectOptionsNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectOptionsNamespacedPodProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectOptionsNamespacedPodProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectOptionsNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectOptionsNamespacedPodProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectOptionsNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectOptionsNamespacedPodProxy contentType res accept Source # | |
HasOptionalParam ConnectHeadNodeProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectHeadNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectHeadNodeProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectHeadNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectHeadNodeProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectHeadNodeProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectHeadNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectHeadNodeProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectHeadNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectHeadNodeProxy contentType res accept Source # | |
HasOptionalParam ConnectHeadNamespacedServiceProxyWithPath Path2 Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectHeadNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectHeadNamespacedServiceProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectHeadNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectHeadNamespacedServiceProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectHeadNamespacedServiceProxy Path Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectHeadNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectHeadNamespacedServiceProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectHeadNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectHeadNamespacedServiceProxy contentType res accept Source # | |
HasOptionalParam ConnectHeadNamespacedPodProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectHeadNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectHeadNamespacedPodProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectHeadNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectHeadNamespacedPodProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectHeadNamespacedPodProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectHeadNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectHeadNamespacedPodProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectHeadNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectHeadNamespacedPodProxy contentType res accept Source # | |
HasOptionalParam ConnectGetNodeProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectGetNodeProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectGetNodeProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectGetNodeProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectGetNodeProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectGetNodeProxy contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedServiceProxyWithPath Path2 Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectGetNamespacedServiceProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectGetNamespacedServiceProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedServiceProxy Path Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectGetNamespacedServiceProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectGetNamespacedServiceProxy contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectGetNamespacedPodProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectGetNamespacedPodProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectGetNamespacedPodProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectGetNamespacedPodProxy contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodPortforward Ports Source # | Optional Param "ports" - List of ports to forward Required when using WebSockets |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodPortforward contentType res accept -> Ports -> KubernetesRequest ConnectGetNamespacedPodPortforward contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodPortforward contentType res accept -> Ports -> KubernetesRequest ConnectGetNamespacedPodPortforward contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodExec Tty Source # | Optional Param "tty" - TTY if true indicates that a tty will be allocated for the exec call. Defaults to false. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodExec contentType res accept -> Tty -> KubernetesRequest ConnectGetNamespacedPodExec contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodExec contentType res accept -> Tty -> KubernetesRequest ConnectGetNamespacedPodExec contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodExec Stdout Source # | Optional Param "stdout" - Redirect the standard output stream of the pod for this call. Defaults to true. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodExec contentType res accept -> Stdout -> KubernetesRequest ConnectGetNamespacedPodExec contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodExec contentType res accept -> Stdout -> KubernetesRequest ConnectGetNamespacedPodExec contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodExec Stdin Source # | Optional Param "stdin" - Redirect the standard input stream of the pod for this call. Defaults to false. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodExec contentType res accept -> Stdin -> KubernetesRequest ConnectGetNamespacedPodExec contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodExec contentType res accept -> Stdin -> KubernetesRequest ConnectGetNamespacedPodExec contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodExec Stderr Source # | Optional Param "stderr" - Redirect the standard error stream of the pod for this call. Defaults to true. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodExec contentType res accept -> Stderr -> KubernetesRequest ConnectGetNamespacedPodExec contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodExec contentType res accept -> Stderr -> KubernetesRequest ConnectGetNamespacedPodExec contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodExec Container Source # | Optional Param "container" - Container in which to execute the command. Defaults to only container if there is only one container in the pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodExec contentType res accept -> Container -> KubernetesRequest ConnectGetNamespacedPodExec contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodExec contentType res accept -> Container -> KubernetesRequest ConnectGetNamespacedPodExec contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodExec Command Source # | Optional Param "command" - Command is the remote command to execute. argv array. Not executed within a shell. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodExec contentType res accept -> Command -> KubernetesRequest ConnectGetNamespacedPodExec contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodExec contentType res accept -> Command -> KubernetesRequest ConnectGetNamespacedPodExec contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodAttach Tty Source # | Optional Param "tty" - TTY if true indicates that a tty will be allocated for the attach call. This is passed through the container runtime so the tty is allocated on the worker node by the container runtime. Defaults to false. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept -> Tty -> KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept -> Tty -> KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodAttach Stdout Source # | Optional Param "stdout" - Stdout if true indicates that stdout is to be redirected for the attach call. Defaults to true. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept -> Stdout -> KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept -> Stdout -> KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodAttach Stdin Source # | Optional Param "stdin" - Stdin if true, redirects the standard input stream of the pod for this call. Defaults to false. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept -> Stdin -> KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept -> Stdin -> KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodAttach Stderr Source # | Optional Param "stderr" - Stderr if true indicates that stderr is to be redirected for the attach call. Defaults to true. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept -> Stderr -> KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept -> Stderr -> KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept Source # | |
HasOptionalParam ConnectGetNamespacedPodAttach Container Source # | Optional Param "container" - The container in which to execute the command. Defaults to only container if there is only one container in the pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept -> Container -> KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept Source # (-&-) :: KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept -> Container -> KubernetesRequest ConnectGetNamespacedPodAttach contentType res accept Source # | |
HasOptionalParam ConnectDeleteNodeProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectDeleteNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectDeleteNodeProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectDeleteNodeProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectDeleteNodeProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectDeleteNodeProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to node. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectDeleteNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectDeleteNodeProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectDeleteNodeProxy contentType res accept -> Path -> KubernetesRequest ConnectDeleteNodeProxy contentType res accept Source # | |
HasOptionalParam ConnectDeleteNamespacedServiceProxyWithPath Path2 Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectDeleteNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectDeleteNamespacedServiceProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectDeleteNamespacedServiceProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectDeleteNamespacedServiceProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectDeleteNamespacedServiceProxy Path Source # | Optional Param "path" - Path is the part of URLs that include service endpoints, suffixes, and parameters to use for the current proxy request to service. For example, the whole request URL is http://localhost/api/v1/namespaces/kube-system/services/elasticsearch-logging/_search?q=user:kimchy. Path is _search?q=user:kimchy. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectDeleteNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectDeleteNamespacedServiceProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectDeleteNamespacedServiceProxy contentType res accept -> Path -> KubernetesRequest ConnectDeleteNamespacedServiceProxy contentType res accept Source # | |
HasOptionalParam ConnectDeleteNamespacedPodProxyWithPath Path2 Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectDeleteNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectDeleteNamespacedPodProxyWithPath contentType res accept Source # (-&-) :: KubernetesRequest ConnectDeleteNamespacedPodProxyWithPath contentType res accept -> Path2 -> KubernetesRequest ConnectDeleteNamespacedPodProxyWithPath contentType res accept Source # | |
HasOptionalParam ConnectDeleteNamespacedPodProxy Path Source # | Optional Param "path" - Path is the URL path to use for the current proxy request to pod. |
Defined in Kubernetes.OpenAPI.API.CoreV1 Methods applyOptionalParam :: KubernetesRequest ConnectDeleteNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectDeleteNamespacedPodProxy contentType res accept Source # (-&-) :: KubernetesRequest ConnectDeleteNamespacedPodProxy contentType res accept -> Path -> KubernetesRequest ConnectDeleteNamespacedPodProxy contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedLease contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedLease contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedLease contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedLease FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedLease contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedLease contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedLease contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedLease DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedLease contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedLease contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedLease contentType res accept Source # | |
HasOptionalParam ReadNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedLease contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedLease contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedLease contentType res accept Source # | |
HasOptionalParam ReadNamespacedLease Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedLease contentType res accept -> Export -> KubernetesRequest ReadNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedLease contentType res accept -> Export -> KubernetesRequest ReadNamespacedLease contentType res accept Source # | |
HasOptionalParam ReadNamespacedLease Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedLease contentType res accept -> Exact -> KubernetesRequest ReadNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedLease contentType res accept -> Exact -> KubernetesRequest ReadNamespacedLease contentType res accept Source # | |
HasOptionalParam PatchNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedLease contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedLease contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedLease contentType res accept Source # | |
HasOptionalParam PatchNamespacedLease Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedLease contentType res accept -> Force -> KubernetesRequest PatchNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedLease contentType res accept -> Force -> KubernetesRequest PatchNamespacedLease contentType res accept Source # | |
HasOptionalParam PatchNamespacedLease FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedLease contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedLease contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedLease contentType res accept Source # | |
HasOptionalParam PatchNamespacedLease DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedLease contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedLease contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> Watch -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> Watch -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> Pretty -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> Pretty -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> Limit -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> Limit -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> Continue -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> Continue -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLease PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLease contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLease contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLease contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLease contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLease OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLease contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLease contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLease GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLease contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLease contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLease DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLease contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLease contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam CreateNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLease contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLease contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedLease contentType res accept Source # | |
HasOptionalParam CreateNamespacedLease FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLease contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLease contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedLease contentType res accept Source # | |
HasOptionalParam CreateNamespacedLease DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLease contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLease contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedLease contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedLease contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedLease contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedLease contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedLease FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedLease contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedLease contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedLease contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedLease DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedLease contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedLease contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedLease contentType res accept Source # | |
HasOptionalParam ReadNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedLease contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedLease contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedLease contentType res accept Source # | |
HasOptionalParam ReadNamespacedLease Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedLease contentType res accept -> Export -> KubernetesRequest ReadNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedLease contentType res accept -> Export -> KubernetesRequest ReadNamespacedLease contentType res accept Source # | |
HasOptionalParam ReadNamespacedLease Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedLease contentType res accept -> Exact -> KubernetesRequest ReadNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedLease contentType res accept -> Exact -> KubernetesRequest ReadNamespacedLease contentType res accept Source # | |
HasOptionalParam PatchNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedLease contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedLease contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedLease contentType res accept Source # | |
HasOptionalParam PatchNamespacedLease Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedLease contentType res accept -> Force -> KubernetesRequest PatchNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedLease contentType res accept -> Force -> KubernetesRequest PatchNamespacedLease contentType res accept Source # | |
HasOptionalParam PatchNamespacedLease FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedLease contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedLease contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedLease contentType res accept Source # | |
HasOptionalParam PatchNamespacedLease DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedLease contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedLease contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> Watch -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> Watch -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> Pretty -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> Pretty -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> Limit -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> Limit -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> Continue -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> Continue -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListNamespacedLease AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedLease contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedLease contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedLease contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListLeaseForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListLeaseForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListLeaseForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLease PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLease contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLease contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLease contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLease contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLease OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLease contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLease contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLease GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLease contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLease contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteNamespacedLease DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedLease contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedLease contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedLease Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedLease contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedLease contentType res accept Source # | |
HasOptionalParam CreateNamespacedLease Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLease contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLease contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedLease contentType res accept Source # | |
HasOptionalParam CreateNamespacedLease FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLease contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLease contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedLease contentType res accept Source # | |
HasOptionalParam CreateNamespacedLease DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CoordinationV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLease contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedLease contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLease contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedLease contentType res accept Source # | |
HasOptionalParam ReplaceCertificateSigningRequestStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCertificateSigningRequestStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceCertificateSigningRequestStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCertificateSigningRequestStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceCertificateSigningRequestStatus contentType res accept Source # | |
HasOptionalParam ReplaceCertificateSigningRequestStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCertificateSigningRequestStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceCertificateSigningRequestStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCertificateSigningRequestStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceCertificateSigningRequestStatus contentType res accept Source # | |
HasOptionalParam ReplaceCertificateSigningRequestStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCertificateSigningRequestStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceCertificateSigningRequestStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCertificateSigningRequestStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceCertificateSigningRequestStatus contentType res accept Source # | |
HasOptionalParam ReplaceCertificateSigningRequestApproval Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCertificateSigningRequestApproval contentType res accept -> Pretty -> KubernetesRequest ReplaceCertificateSigningRequestApproval contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCertificateSigningRequestApproval contentType res accept -> Pretty -> KubernetesRequest ReplaceCertificateSigningRequestApproval contentType res accept Source # | |
HasOptionalParam ReplaceCertificateSigningRequestApproval FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCertificateSigningRequestApproval contentType res accept -> FieldManager -> KubernetesRequest ReplaceCertificateSigningRequestApproval contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCertificateSigningRequestApproval contentType res accept -> FieldManager -> KubernetesRequest ReplaceCertificateSigningRequestApproval contentType res accept Source # | |
HasOptionalParam ReplaceCertificateSigningRequestApproval DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCertificateSigningRequestApproval contentType res accept -> DryRun -> KubernetesRequest ReplaceCertificateSigningRequestApproval contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCertificateSigningRequestApproval contentType res accept -> DryRun -> KubernetesRequest ReplaceCertificateSigningRequestApproval contentType res accept Source # | |
HasOptionalParam ReplaceCertificateSigningRequest Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest ReplaceCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest ReplaceCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ReplaceCertificateSigningRequest FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCertificateSigningRequest contentType res accept -> FieldManager -> KubernetesRequest ReplaceCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCertificateSigningRequest contentType res accept -> FieldManager -> KubernetesRequest ReplaceCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ReplaceCertificateSigningRequest DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCertificateSigningRequest contentType res accept -> DryRun -> KubernetesRequest ReplaceCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCertificateSigningRequest contentType res accept -> DryRun -> KubernetesRequest ReplaceCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ReadCertificateSigningRequestStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCertificateSigningRequestStatus contentType res accept -> Pretty -> KubernetesRequest ReadCertificateSigningRequestStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadCertificateSigningRequestStatus contentType res accept -> Pretty -> KubernetesRequest ReadCertificateSigningRequestStatus contentType res accept Source # | |
HasOptionalParam ReadCertificateSigningRequest Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest ReadCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ReadCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest ReadCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ReadCertificateSigningRequest Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCertificateSigningRequest contentType res accept -> Export -> KubernetesRequest ReadCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ReadCertificateSigningRequest contentType res accept -> Export -> KubernetesRequest ReadCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ReadCertificateSigningRequest Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCertificateSigningRequest contentType res accept -> Exact -> KubernetesRequest ReadCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ReadCertificateSigningRequest contentType res accept -> Exact -> KubernetesRequest ReadCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam PatchCertificateSigningRequestStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept -> Pretty -> KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept -> Pretty -> KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept Source # | |
HasOptionalParam PatchCertificateSigningRequestStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept -> Force -> KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept -> Force -> KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept Source # | |
HasOptionalParam PatchCertificateSigningRequestStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept -> FieldManager -> KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept -> FieldManager -> KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept Source # | |
HasOptionalParam PatchCertificateSigningRequestStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept -> DryRun -> KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept -> DryRun -> KubernetesRequest PatchCertificateSigningRequestStatus contentType res accept Source # | |
HasOptionalParam PatchCertificateSigningRequest Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest PatchCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest PatchCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest PatchCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam PatchCertificateSigningRequest Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCertificateSigningRequest contentType res accept -> Force -> KubernetesRequest PatchCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest PatchCertificateSigningRequest contentType res accept -> Force -> KubernetesRequest PatchCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam PatchCertificateSigningRequest FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCertificateSigningRequest contentType res accept -> FieldManager -> KubernetesRequest PatchCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest PatchCertificateSigningRequest contentType res accept -> FieldManager -> KubernetesRequest PatchCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam PatchCertificateSigningRequest DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCertificateSigningRequest contentType res accept -> DryRun -> KubernetesRequest PatchCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest PatchCertificateSigningRequest contentType res accept -> DryRun -> KubernetesRequest PatchCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ListCertificateSigningRequest Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> Watch -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> Watch -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ListCertificateSigningRequest TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ListCertificateSigningRequest ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> ResourceVersion -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> ResourceVersion -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ListCertificateSigningRequest Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ListCertificateSigningRequest Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> Limit -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> Limit -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ListCertificateSigningRequest LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> LabelSelector -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> LabelSelector -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ListCertificateSigningRequest FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> FieldSelector -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> FieldSelector -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ListCertificateSigningRequest Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> Continue -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> Continue -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ListCertificateSigningRequest AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest ListCertificateSigningRequest contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCollectionCertificateSigningRequest TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCollectionCertificateSigningRequest ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCollectionCertificateSigningRequest PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCollectionCertificateSigningRequest Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCollectionCertificateSigningRequest OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCollectionCertificateSigningRequest Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> Limit -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> Limit -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCollectionCertificateSigningRequest LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCollectionCertificateSigningRequest GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCollectionCertificateSigningRequest FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCollectionCertificateSigningRequest DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCollectionCertificateSigningRequest Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> Continue -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept -> Continue -> KubernetesRequest DeleteCollectionCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCertificateSigningRequest PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCertificateSigningRequest contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCertificateSigningRequest contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCertificateSigningRequest Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest DeleteCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest DeleteCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCertificateSigningRequest OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCertificateSigningRequest contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCertificateSigningRequest contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCertificateSigningRequest GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCertificateSigningRequest contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCertificateSigningRequest contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam DeleteCertificateSigningRequest DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCertificateSigningRequest contentType res accept -> DryRun -> KubernetesRequest DeleteCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest DeleteCertificateSigningRequest contentType res accept -> DryRun -> KubernetesRequest DeleteCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam CreateCertificateSigningRequest Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest CreateCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest CreateCertificateSigningRequest contentType res accept -> Pretty -> KubernetesRequest CreateCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam CreateCertificateSigningRequest FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateCertificateSigningRequest contentType res accept -> FieldManager -> KubernetesRequest CreateCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest CreateCertificateSigningRequest contentType res accept -> FieldManager -> KubernetesRequest CreateCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam CreateCertificateSigningRequest DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.CertificatesV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateCertificateSigningRequest contentType res accept -> DryRun -> KubernetesRequest CreateCertificateSigningRequest contentType res accept Source # (-&-) :: KubernetesRequest CreateCertificateSigningRequest contentType res accept -> DryRun -> KubernetesRequest CreateCertificateSigningRequest contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCronJobStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCronJobStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCronJobStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCronJob FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCronJob contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCronJob contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCronJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ReadNamespacedCronJobStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedCronJobStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedCronJobStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ReadNamespacedCronJob Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedCronJob contentType res accept -> Export -> KubernetesRequest ReadNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedCronJob contentType res accept -> Export -> KubernetesRequest ReadNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ReadNamespacedCronJob Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedCronJob contentType res accept -> Exact -> KubernetesRequest ReadNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedCronJob contentType res accept -> Exact -> KubernetesRequest ReadNamespacedCronJob contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJobStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJobStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJobStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJobStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJob Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> Force -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> Force -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJob FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Watch -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Watch -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Limit -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Limit -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Continue -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Continue -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCronJob PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCronJob OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCronJob GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCronJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam CreateNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedCronJob contentType res accept Source # | |
HasOptionalParam CreateNamespacedCronJob FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedCronJob contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedCronJob contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedCronJob contentType res accept Source # | |
HasOptionalParam CreateNamespacedCronJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV2alpha1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCronJobStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCronJobStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCronJobStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCronJob FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCronJob contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCronJob contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedCronJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ReadNamespacedCronJobStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedCronJobStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedCronJobStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ReadNamespacedCronJob Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedCronJob contentType res accept -> Export -> KubernetesRequest ReadNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedCronJob contentType res accept -> Export -> KubernetesRequest ReadNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ReadNamespacedCronJob Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedCronJob contentType res accept -> Exact -> KubernetesRequest ReadNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedCronJob contentType res accept -> Exact -> KubernetesRequest ReadNamespacedCronJob contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJobStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJobStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJobStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJobStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJobStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCronJobStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJob Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> Force -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> Force -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJob FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # | |
HasOptionalParam PatchNamespacedCronJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Watch -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Watch -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Limit -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Limit -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Continue -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> Continue -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListNamespacedCronJob AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedCronJob contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedCronJob contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListCronJobForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListCronJobForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCronJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCronJob PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCronJob OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCronJob GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteNamespacedCronJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedCronJob Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedCronJob contentType res accept Source # | |
HasOptionalParam CreateNamespacedCronJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedCronJob contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedCronJob contentType res accept Source # | |
HasOptionalParam CreateNamespacedCronJob FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedCronJob contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedCronJob contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedCronJob contentType res accept Source # | |
HasOptionalParam CreateNamespacedCronJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedCronJob contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedCronJob contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedCronJob contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedJobStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedJobStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedJobStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedJobStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedJobStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedJobStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedJobStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedJobStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedJobStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedJobStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedJobStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedJobStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedJobStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedJobStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedJobStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedJob contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedJob contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedJob contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedJob FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedJob contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedJob contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedJob contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedJob contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedJob contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedJob contentType res accept Source # | |
HasOptionalParam ReadNamespacedJobStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedJobStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedJobStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedJobStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedJobStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedJob contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedJob contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedJob contentType res accept Source # | |
HasOptionalParam ReadNamespacedJob Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedJob contentType res accept -> Export -> KubernetesRequest ReadNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedJob contentType res accept -> Export -> KubernetesRequest ReadNamespacedJob contentType res accept Source # | |
HasOptionalParam ReadNamespacedJob Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedJob contentType res accept -> Exact -> KubernetesRequest ReadNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedJob contentType res accept -> Exact -> KubernetesRequest ReadNamespacedJob contentType res accept Source # | |
HasOptionalParam PatchNamespacedJobStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedJobStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedJobStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedJobStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedJobStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedJobStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedJobStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedJobStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedJobStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedJobStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedJobStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedJobStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedJobStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedJobStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedJobStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedJobStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedJobStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedJobStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedJobStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedJobStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedJob contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedJob contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedJob contentType res accept Source # | |
HasOptionalParam PatchNamespacedJob Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedJob contentType res accept -> Force -> KubernetesRequest PatchNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedJob contentType res accept -> Force -> KubernetesRequest PatchNamespacedJob contentType res accept Source # | |
HasOptionalParam PatchNamespacedJob FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedJob contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedJob contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedJob contentType res accept Source # | |
HasOptionalParam PatchNamespacedJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedJob contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedJob contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedJob contentType res accept Source # | |
HasOptionalParam ListNamespacedJob Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedJob contentType res accept -> Watch -> KubernetesRequest ListNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedJob contentType res accept -> Watch -> KubernetesRequest ListNamespacedJob contentType res accept Source # | |
HasOptionalParam ListNamespacedJob TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedJob contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedJob contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedJob contentType res accept Source # | |
HasOptionalParam ListNamespacedJob ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedJob contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedJob contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedJob contentType res accept Source # | |
HasOptionalParam ListNamespacedJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedJob contentType res accept -> Pretty -> KubernetesRequest ListNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedJob contentType res accept -> Pretty -> KubernetesRequest ListNamespacedJob contentType res accept Source # | |
HasOptionalParam ListNamespacedJob Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedJob contentType res accept -> Limit -> KubernetesRequest ListNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedJob contentType res accept -> Limit -> KubernetesRequest ListNamespacedJob contentType res accept Source # | |
HasOptionalParam ListNamespacedJob LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedJob contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedJob contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedJob contentType res accept Source # | |
HasOptionalParam ListNamespacedJob FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedJob contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedJob contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedJob contentType res accept Source # | |
HasOptionalParam ListNamespacedJob Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedJob contentType res accept -> Continue -> KubernetesRequest ListNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedJob contentType res accept -> Continue -> KubernetesRequest ListNamespacedJob contentType res accept Source # | |
HasOptionalParam ListNamespacedJob AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedJob contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedJob contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedJob contentType res accept Source # | |
HasOptionalParam ListJobForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListJobForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListJobForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListJobForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListJobForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListJobForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListJobForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListJobForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListJobForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListJobForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListJobForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedJob PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedJob contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedJob contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteNamespacedJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedJob contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedJob contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteNamespacedJob OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedJob contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedJob contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteNamespacedJob GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedJob contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedJob contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteNamespacedJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedJob contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedJob contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedJob TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedJob ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedJob PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedJob OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedJob Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedJob LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedJob GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedJob FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedJob Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedJob contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedJob contentType res accept Source # | |
HasOptionalParam CreateNamespacedJob Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedJob contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedJob contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedJob contentType res accept Source # | |
HasOptionalParam CreateNamespacedJob FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedJob contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedJob contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedJob contentType res accept Source # | |
HasOptionalParam CreateNamespacedJob DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.BatchV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedJob contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedJob contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedJob contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedJob contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscalerStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscalerStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscalerStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscaler FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReadNamespacedHorizontalPodAutoscalerStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReadNamespacedHorizontalPodAutoscaler Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Export -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Export -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReadNamespacedHorizontalPodAutoscaler Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Exact -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Exact -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscalerStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscalerStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscalerStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscalerStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscaler Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> Force -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> Force -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscaler FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Watch -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Watch -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Limit -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Limit -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Continue -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Continue -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam CreateNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam CreateNamespacedHorizontalPodAutoscaler FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam CreateNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscalerStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscalerStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscalerStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscaler FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReadNamespacedHorizontalPodAutoscalerStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReadNamespacedHorizontalPodAutoscaler Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Export -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Export -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReadNamespacedHorizontalPodAutoscaler Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Exact -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Exact -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscalerStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscalerStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscalerStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscalerStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscaler Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> Force -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> Force -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscaler FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Watch -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Watch -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Limit -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Limit -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Continue -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Continue -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam CreateNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam CreateNamespacedHorizontalPodAutoscaler FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam CreateNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV2beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscalerStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscalerStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscalerStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscaler FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReadNamespacedHorizontalPodAutoscalerStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReadNamespacedHorizontalPodAutoscaler Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Export -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Export -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ReadNamespacedHorizontalPodAutoscaler Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Exact -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept -> Exact -> KubernetesRequest ReadNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscalerStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscalerStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscalerStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscalerStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedHorizontalPodAutoscalerStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscaler Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> Force -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> Force -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscaler FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam PatchNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Watch -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Watch -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Limit -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Limit -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Continue -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> Continue -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListNamespacedHorizontalPodAutoscaler AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListHorizontalPodAutoscalerForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListHorizontalPodAutoscalerForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedHorizontalPodAutoscaler Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam CreateNamespacedHorizontalPodAutoscaler Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam CreateNamespacedHorizontalPodAutoscaler FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam CreateNamespacedHorizontalPodAutoscaler DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AutoscalingV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedHorizontalPodAutoscaler contentType res accept Source # | |
HasOptionalParam CreateSubjectAccessReview Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateSubjectAccessReview contentType res accept -> Pretty -> KubernetesRequest CreateSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSubjectAccessReview contentType res accept -> Pretty -> KubernetesRequest CreateSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateSubjectAccessReview FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateSubjectAccessReview contentType res accept -> FieldManager -> KubernetesRequest CreateSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSubjectAccessReview contentType res accept -> FieldManager -> KubernetesRequest CreateSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateSubjectAccessReview DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateSubjectAccessReview contentType res accept -> DryRun -> KubernetesRequest CreateSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSubjectAccessReview contentType res accept -> DryRun -> KubernetesRequest CreateSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateSelfSubjectRulesReview Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateSelfSubjectRulesReview contentType res accept -> Pretty -> KubernetesRequest CreateSelfSubjectRulesReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSelfSubjectRulesReview contentType res accept -> Pretty -> KubernetesRequest CreateSelfSubjectRulesReview contentType res accept Source # | |
HasOptionalParam CreateSelfSubjectRulesReview FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateSelfSubjectRulesReview contentType res accept -> FieldManager -> KubernetesRequest CreateSelfSubjectRulesReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSelfSubjectRulesReview contentType res accept -> FieldManager -> KubernetesRequest CreateSelfSubjectRulesReview contentType res accept Source # | |
HasOptionalParam CreateSelfSubjectRulesReview DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateSelfSubjectRulesReview contentType res accept -> DryRun -> KubernetesRequest CreateSelfSubjectRulesReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSelfSubjectRulesReview contentType res accept -> DryRun -> KubernetesRequest CreateSelfSubjectRulesReview contentType res accept Source # | |
HasOptionalParam CreateSelfSubjectAccessReview Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateSelfSubjectAccessReview contentType res accept -> Pretty -> KubernetesRequest CreateSelfSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSelfSubjectAccessReview contentType res accept -> Pretty -> KubernetesRequest CreateSelfSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateSelfSubjectAccessReview FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateSelfSubjectAccessReview contentType res accept -> FieldManager -> KubernetesRequest CreateSelfSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSelfSubjectAccessReview contentType res accept -> FieldManager -> KubernetesRequest CreateSelfSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateSelfSubjectAccessReview DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateSelfSubjectAccessReview contentType res accept -> DryRun -> KubernetesRequest CreateSelfSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSelfSubjectAccessReview contentType res accept -> DryRun -> KubernetesRequest CreateSelfSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateNamespacedLocalSubjectAccessReview Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateNamespacedLocalSubjectAccessReview FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateNamespacedLocalSubjectAccessReview DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateSubjectAccessReview Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateSubjectAccessReview contentType res accept -> Pretty -> KubernetesRequest CreateSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSubjectAccessReview contentType res accept -> Pretty -> KubernetesRequest CreateSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateSubjectAccessReview FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateSubjectAccessReview contentType res accept -> FieldManager -> KubernetesRequest CreateSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSubjectAccessReview contentType res accept -> FieldManager -> KubernetesRequest CreateSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateSubjectAccessReview DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateSubjectAccessReview contentType res accept -> DryRun -> KubernetesRequest CreateSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSubjectAccessReview contentType res accept -> DryRun -> KubernetesRequest CreateSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateSelfSubjectRulesReview Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateSelfSubjectRulesReview contentType res accept -> Pretty -> KubernetesRequest CreateSelfSubjectRulesReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSelfSubjectRulesReview contentType res accept -> Pretty -> KubernetesRequest CreateSelfSubjectRulesReview contentType res accept Source # | |
HasOptionalParam CreateSelfSubjectRulesReview FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateSelfSubjectRulesReview contentType res accept -> FieldManager -> KubernetesRequest CreateSelfSubjectRulesReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSelfSubjectRulesReview contentType res accept -> FieldManager -> KubernetesRequest CreateSelfSubjectRulesReview contentType res accept Source # | |
HasOptionalParam CreateSelfSubjectRulesReview DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateSelfSubjectRulesReview contentType res accept -> DryRun -> KubernetesRequest CreateSelfSubjectRulesReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSelfSubjectRulesReview contentType res accept -> DryRun -> KubernetesRequest CreateSelfSubjectRulesReview contentType res accept Source # | |
HasOptionalParam CreateSelfSubjectAccessReview Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateSelfSubjectAccessReview contentType res accept -> Pretty -> KubernetesRequest CreateSelfSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSelfSubjectAccessReview contentType res accept -> Pretty -> KubernetesRequest CreateSelfSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateSelfSubjectAccessReview FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateSelfSubjectAccessReview contentType res accept -> FieldManager -> KubernetesRequest CreateSelfSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSelfSubjectAccessReview contentType res accept -> FieldManager -> KubernetesRequest CreateSelfSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateSelfSubjectAccessReview DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateSelfSubjectAccessReview contentType res accept -> DryRun -> KubernetesRequest CreateSelfSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateSelfSubjectAccessReview contentType res accept -> DryRun -> KubernetesRequest CreateSelfSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateNamespacedLocalSubjectAccessReview Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateNamespacedLocalSubjectAccessReview FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateNamespacedLocalSubjectAccessReview DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuthorizationV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedLocalSubjectAccessReview contentType res accept Source # | |
HasOptionalParam CreateTokenReview Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuthenticationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateTokenReview contentType res accept -> Pretty -> KubernetesRequest CreateTokenReview contentType res accept Source # (-&-) :: KubernetesRequest CreateTokenReview contentType res accept -> Pretty -> KubernetesRequest CreateTokenReview contentType res accept Source # | |
HasOptionalParam CreateTokenReview FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuthenticationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateTokenReview contentType res accept -> FieldManager -> KubernetesRequest CreateTokenReview contentType res accept Source # (-&-) :: KubernetesRequest CreateTokenReview contentType res accept -> FieldManager -> KubernetesRequest CreateTokenReview contentType res accept Source # | |
HasOptionalParam CreateTokenReview DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuthenticationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateTokenReview contentType res accept -> DryRun -> KubernetesRequest CreateTokenReview contentType res accept Source # (-&-) :: KubernetesRequest CreateTokenReview contentType res accept -> DryRun -> KubernetesRequest CreateTokenReview contentType res accept Source # | |
HasOptionalParam CreateTokenReview Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuthenticationV1 Methods applyOptionalParam :: KubernetesRequest CreateTokenReview contentType res accept -> Pretty -> KubernetesRequest CreateTokenReview contentType res accept Source # (-&-) :: KubernetesRequest CreateTokenReview contentType res accept -> Pretty -> KubernetesRequest CreateTokenReview contentType res accept Source # | |
HasOptionalParam CreateTokenReview FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuthenticationV1 Methods applyOptionalParam :: KubernetesRequest CreateTokenReview contentType res accept -> FieldManager -> KubernetesRequest CreateTokenReview contentType res accept Source # (-&-) :: KubernetesRequest CreateTokenReview contentType res accept -> FieldManager -> KubernetesRequest CreateTokenReview contentType res accept Source # | |
HasOptionalParam CreateTokenReview DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuthenticationV1 Methods applyOptionalParam :: KubernetesRequest CreateTokenReview contentType res accept -> DryRun -> KubernetesRequest CreateTokenReview contentType res accept Source # (-&-) :: KubernetesRequest CreateTokenReview contentType res accept -> DryRun -> KubernetesRequest CreateTokenReview contentType res accept Source # | |
HasOptionalParam ReplaceAuditSink Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceAuditSink contentType res accept -> Pretty -> KubernetesRequest ReplaceAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAuditSink contentType res accept -> Pretty -> KubernetesRequest ReplaceAuditSink contentType res accept Source # | |
HasOptionalParam ReplaceAuditSink FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceAuditSink contentType res accept -> FieldManager -> KubernetesRequest ReplaceAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAuditSink contentType res accept -> FieldManager -> KubernetesRequest ReplaceAuditSink contentType res accept Source # | |
HasOptionalParam ReplaceAuditSink DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReplaceAuditSink contentType res accept -> DryRun -> KubernetesRequest ReplaceAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAuditSink contentType res accept -> DryRun -> KubernetesRequest ReplaceAuditSink contentType res accept Source # | |
HasOptionalParam ReadAuditSink Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadAuditSink contentType res accept -> Pretty -> KubernetesRequest ReadAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ReadAuditSink contentType res accept -> Pretty -> KubernetesRequest ReadAuditSink contentType res accept Source # | |
HasOptionalParam ReadAuditSink Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadAuditSink contentType res accept -> Export -> KubernetesRequest ReadAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ReadAuditSink contentType res accept -> Export -> KubernetesRequest ReadAuditSink contentType res accept Source # | |
HasOptionalParam ReadAuditSink Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ReadAuditSink contentType res accept -> Exact -> KubernetesRequest ReadAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ReadAuditSink contentType res accept -> Exact -> KubernetesRequest ReadAuditSink contentType res accept Source # | |
HasOptionalParam PatchAuditSink Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchAuditSink contentType res accept -> Pretty -> KubernetesRequest PatchAuditSink contentType res accept Source # (-&-) :: KubernetesRequest PatchAuditSink contentType res accept -> Pretty -> KubernetesRequest PatchAuditSink contentType res accept Source # | |
HasOptionalParam PatchAuditSink Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchAuditSink contentType res accept -> Force -> KubernetesRequest PatchAuditSink contentType res accept Source # (-&-) :: KubernetesRequest PatchAuditSink contentType res accept -> Force -> KubernetesRequest PatchAuditSink contentType res accept Source # | |
HasOptionalParam PatchAuditSink FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchAuditSink contentType res accept -> FieldManager -> KubernetesRequest PatchAuditSink contentType res accept Source # (-&-) :: KubernetesRequest PatchAuditSink contentType res accept -> FieldManager -> KubernetesRequest PatchAuditSink contentType res accept Source # | |
HasOptionalParam PatchAuditSink DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest PatchAuditSink contentType res accept -> DryRun -> KubernetesRequest PatchAuditSink contentType res accept Source # (-&-) :: KubernetesRequest PatchAuditSink contentType res accept -> DryRun -> KubernetesRequest PatchAuditSink contentType res accept Source # | |
HasOptionalParam ListAuditSink Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListAuditSink contentType res accept -> Watch -> KubernetesRequest ListAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ListAuditSink contentType res accept -> Watch -> KubernetesRequest ListAuditSink contentType res accept Source # | |
HasOptionalParam ListAuditSink TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListAuditSink contentType res accept -> TimeoutSeconds -> KubernetesRequest ListAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ListAuditSink contentType res accept -> TimeoutSeconds -> KubernetesRequest ListAuditSink contentType res accept Source # | |
HasOptionalParam ListAuditSink ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListAuditSink contentType res accept -> ResourceVersion -> KubernetesRequest ListAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ListAuditSink contentType res accept -> ResourceVersion -> KubernetesRequest ListAuditSink contentType res accept Source # | |
HasOptionalParam ListAuditSink Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListAuditSink contentType res accept -> Pretty -> KubernetesRequest ListAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ListAuditSink contentType res accept -> Pretty -> KubernetesRequest ListAuditSink contentType res accept Source # | |
HasOptionalParam ListAuditSink Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListAuditSink contentType res accept -> Limit -> KubernetesRequest ListAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ListAuditSink contentType res accept -> Limit -> KubernetesRequest ListAuditSink contentType res accept Source # | |
HasOptionalParam ListAuditSink LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListAuditSink contentType res accept -> LabelSelector -> KubernetesRequest ListAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ListAuditSink contentType res accept -> LabelSelector -> KubernetesRequest ListAuditSink contentType res accept Source # | |
HasOptionalParam ListAuditSink FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListAuditSink contentType res accept -> FieldSelector -> KubernetesRequest ListAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ListAuditSink contentType res accept -> FieldSelector -> KubernetesRequest ListAuditSink contentType res accept Source # | |
HasOptionalParam ListAuditSink Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListAuditSink contentType res accept -> Continue -> KubernetesRequest ListAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ListAuditSink contentType res accept -> Continue -> KubernetesRequest ListAuditSink contentType res accept Source # | |
HasOptionalParam ListAuditSink AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest ListAuditSink contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListAuditSink contentType res accept Source # (-&-) :: KubernetesRequest ListAuditSink contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListAuditSink contentType res accept Source # | |
HasOptionalParam DeleteCollectionAuditSink TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # | |
HasOptionalParam DeleteCollectionAuditSink ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # | |
HasOptionalParam DeleteCollectionAuditSink PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # | |
HasOptionalParam DeleteCollectionAuditSink Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # | |
HasOptionalParam DeleteCollectionAuditSink OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # | |
HasOptionalParam DeleteCollectionAuditSink Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> Limit -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> Limit -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # | |
HasOptionalParam DeleteCollectionAuditSink LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # | |
HasOptionalParam DeleteCollectionAuditSink GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # | |
HasOptionalParam DeleteCollectionAuditSink FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # | |
HasOptionalParam DeleteCollectionAuditSink DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # | |
HasOptionalParam DeleteCollectionAuditSink Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> Continue -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAuditSink contentType res accept -> Continue -> KubernetesRequest DeleteCollectionAuditSink contentType res accept Source # | |
HasOptionalParam DeleteAuditSink PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteAuditSink contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteAuditSink contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteAuditSink contentType res accept Source # | |
HasOptionalParam DeleteAuditSink Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteAuditSink contentType res accept -> Pretty -> KubernetesRequest DeleteAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteAuditSink contentType res accept -> Pretty -> KubernetesRequest DeleteAuditSink contentType res accept Source # | |
HasOptionalParam DeleteAuditSink OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteAuditSink contentType res accept -> OrphanDependents -> KubernetesRequest DeleteAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteAuditSink contentType res accept -> OrphanDependents -> KubernetesRequest DeleteAuditSink contentType res accept Source # | |
HasOptionalParam DeleteAuditSink GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteAuditSink contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteAuditSink contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteAuditSink contentType res accept Source # | |
HasOptionalParam DeleteAuditSink DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest DeleteAuditSink contentType res accept -> DryRun -> KubernetesRequest DeleteAuditSink contentType res accept Source # (-&-) :: KubernetesRequest DeleteAuditSink contentType res accept -> DryRun -> KubernetesRequest DeleteAuditSink contentType res accept Source # | |
HasOptionalParam CreateAuditSink Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateAuditSink contentType res accept -> Pretty -> KubernetesRequest CreateAuditSink contentType res accept Source # (-&-) :: KubernetesRequest CreateAuditSink contentType res accept -> Pretty -> KubernetesRequest CreateAuditSink contentType res accept Source # | |
HasOptionalParam CreateAuditSink FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateAuditSink contentType res accept -> FieldManager -> KubernetesRequest CreateAuditSink contentType res accept Source # (-&-) :: KubernetesRequest CreateAuditSink contentType res accept -> FieldManager -> KubernetesRequest CreateAuditSink contentType res accept Source # | |
HasOptionalParam CreateAuditSink DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AuditregistrationV1alpha1 Methods applyOptionalParam :: KubernetesRequest CreateAuditSink contentType res accept -> DryRun -> KubernetesRequest CreateAuditSink contentType res accept Source # (-&-) :: KubernetesRequest CreateAuditSink contentType res accept -> DryRun -> KubernetesRequest CreateAuditSink contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeployment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSetStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedControllerRevision FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSet Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSet Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSet Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSet Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeploymentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeploymentScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeployment Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Export -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Export -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeployment Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReadNamespacedDaemonSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedDaemonSet Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedDaemonSet Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReadNamespacedControllerRevision Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Export -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Export -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReadNamespacedControllerRevision Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Exact -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Exact -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSet Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSet FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSet Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSet FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSetStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSetStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSet Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSet FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam PatchNamespacedControllerRevision Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> Force -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> Force -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam PatchNamespacedControllerRevision FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam PatchNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Watch -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Watch -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Watch -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Watch -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Limit -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Limit -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Continue -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Continue -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam CreateNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedStatefulSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedReplicaSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeployment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # | |
HasOptionalParam CreateNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedDaemonSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam CreateNamespacedControllerRevision FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam CreateNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta2 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeployment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedControllerRevision FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSet Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSet Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeploymentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeploymentScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeployment Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Export -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Export -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeployment Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReadNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReadNamespacedControllerRevision Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Export -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Export -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReadNamespacedControllerRevision Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Exact -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Exact -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSet Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSet FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam PatchNamespacedControllerRevision Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> Force -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> Force -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam PatchNamespacedControllerRevision FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam PatchNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Watch -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Watch -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Watch -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Watch -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Limit -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Limit -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Continue -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Continue -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam CreateNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedStatefulSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeploymentRollback Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeploymentRollback FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeploymentRollback DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDeploymentRollback contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeployment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # | |
HasOptionalParam CreateNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam CreateNamespacedControllerRevision FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam CreateNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSetScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSetScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentScale FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeploymentScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeployment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSetStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedControllerRevision FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReplaceNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest ReplaceNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSet Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedStatefulSet Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedStatefulSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSet Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedReplicaSet Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedReplicaSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeploymentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeploymentScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeployment Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Export -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Export -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReadNamespacedDeployment Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDeployment contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ReadNamespacedDaemonSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam ReadNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedDaemonSet Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Export -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedDaemonSet Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedDaemonSet contentType res accept -> Exact -> KubernetesRequest ReadNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ReadNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReadNamespacedControllerRevision Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Export -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Export -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReadNamespacedControllerRevision Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Exact -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ReadNamespacedControllerRevision contentType res accept -> Exact -> KubernetesRequest ReadNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSetScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSet Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSet FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSetScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSetScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSet Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSet FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeploymentScale DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeploymentScale contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeploymentScale contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> Force -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDeployment contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSetStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSetStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> Force -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSetStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSetStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDaemonSetStatus contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSet Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> Force -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSet FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam PatchNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam PatchNamespacedControllerRevision Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> Force -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> Force -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam PatchNamespacedControllerRevision FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam PatchNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest PatchNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest PatchNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListStatefulSetForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListStatefulSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListReplicaSetForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListReplicaSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedStatefulSet AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedStatefulSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedReplicaSet AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedReplicaSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Watch -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Watch -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDeployment AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDeployment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDeployment contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDeployment contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Watch -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Limit -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> Continue -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedDaemonSet AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedDaemonSet contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Watch -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Watch -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> TimeoutSeconds -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> ResourceVersion -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Limit -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Limit -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> LabelSelector -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> FieldSelector -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Continue -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> Continue -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListNamespacedControllerRevision AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest ListNamespacedControllerRevision contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDeploymentForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDeploymentForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDeploymentForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListDaemonSetForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListDaemonSetForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Watch -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> TimeoutSeconds -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> ResourceVersion -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Pretty -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Limit -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> LabelSelector -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> FieldSelector -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> Continue -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam ListControllerRevisionForAllNamespaces AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # (-&-) :: KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListControllerRevisionForAllNamespaces contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> OrphanDependents -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest DeleteNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedStatefulSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedReplicaSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDeployment Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDeployment contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedDaemonSet Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Limit -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam DeleteCollectionNamespacedControllerRevision Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept -> Continue -> KubernetesRequest DeleteCollectionNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam CreateNamespacedStatefulSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedStatefulSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedStatefulSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedStatefulSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedStatefulSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedReplicaSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedReplicaSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedReplicaSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedReplicaSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedReplicaSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeployment Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeployment FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # | |
HasOptionalParam CreateNamespacedDeployment DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDeployment contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDeployment contentType res accept Source # | |
HasOptionalParam CreateNamespacedDaemonSet Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedDaemonSet FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedDaemonSet DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedDaemonSet contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedDaemonSet contentType res accept Source # | |
HasOptionalParam CreateNamespacedControllerRevision Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> Pretty -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam CreateNamespacedControllerRevision FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> FieldManager -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam CreateNamespacedControllerRevision DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AppsV1 Methods applyOptionalParam :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # (-&-) :: KubernetesRequest CreateNamespacedControllerRevision contentType res accept -> DryRun -> KubernetesRequest CreateNamespacedControllerRevision contentType res accept Source # | |
HasOptionalParam ReplaceAPIServiceStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceAPIServiceStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAPIServiceStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceAPIServiceStatus contentType res accept Source # | |
HasOptionalParam ReplaceAPIServiceStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceAPIServiceStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAPIServiceStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceAPIServiceStatus contentType res accept Source # | |
HasOptionalParam ReplaceAPIServiceStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceAPIServiceStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAPIServiceStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceAPIServiceStatus contentType res accept Source # | |
HasOptionalParam ReplaceAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceAPIService contentType res accept -> Pretty -> KubernetesRequest ReplaceAPIService contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAPIService contentType res accept -> Pretty -> KubernetesRequest ReplaceAPIService contentType res accept Source # | |
HasOptionalParam ReplaceAPIService FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceAPIService contentType res accept -> FieldManager -> KubernetesRequest ReplaceAPIService contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAPIService contentType res accept -> FieldManager -> KubernetesRequest ReplaceAPIService contentType res accept Source # | |
HasOptionalParam ReplaceAPIService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceAPIService contentType res accept -> DryRun -> KubernetesRequest ReplaceAPIService contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAPIService contentType res accept -> DryRun -> KubernetesRequest ReplaceAPIService contentType res accept Source # | |
HasOptionalParam ReadAPIServiceStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadAPIServiceStatus contentType res accept -> Pretty -> KubernetesRequest ReadAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadAPIServiceStatus contentType res accept -> Pretty -> KubernetesRequest ReadAPIServiceStatus contentType res accept Source # | |
HasOptionalParam ReadAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadAPIService contentType res accept -> Pretty -> KubernetesRequest ReadAPIService contentType res accept Source # (-&-) :: KubernetesRequest ReadAPIService contentType res accept -> Pretty -> KubernetesRequest ReadAPIService contentType res accept Source # | |
HasOptionalParam ReadAPIService Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadAPIService contentType res accept -> Export -> KubernetesRequest ReadAPIService contentType res accept Source # (-&-) :: KubernetesRequest ReadAPIService contentType res accept -> Export -> KubernetesRequest ReadAPIService contentType res accept Source # | |
HasOptionalParam ReadAPIService Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadAPIService contentType res accept -> Exact -> KubernetesRequest ReadAPIService contentType res accept Source # (-&-) :: KubernetesRequest ReadAPIService contentType res accept -> Exact -> KubernetesRequest ReadAPIService contentType res accept Source # | |
HasOptionalParam PatchAPIServiceStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> Pretty -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> Pretty -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # | |
HasOptionalParam PatchAPIServiceStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> Force -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> Force -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # | |
HasOptionalParam PatchAPIServiceStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> FieldManager -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> FieldManager -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # | |
HasOptionalParam PatchAPIServiceStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> DryRun -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> DryRun -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # | |
HasOptionalParam PatchAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchAPIService contentType res accept -> Pretty -> KubernetesRequest PatchAPIService contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIService contentType res accept -> Pretty -> KubernetesRequest PatchAPIService contentType res accept Source # | |
HasOptionalParam PatchAPIService Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchAPIService contentType res accept -> Force -> KubernetesRequest PatchAPIService contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIService contentType res accept -> Force -> KubernetesRequest PatchAPIService contentType res accept Source # | |
HasOptionalParam PatchAPIService FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchAPIService contentType res accept -> FieldManager -> KubernetesRequest PatchAPIService contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIService contentType res accept -> FieldManager -> KubernetesRequest PatchAPIService contentType res accept Source # | |
HasOptionalParam PatchAPIService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchAPIService contentType res accept -> DryRun -> KubernetesRequest PatchAPIService contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIService contentType res accept -> DryRun -> KubernetesRequest PatchAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> Watch -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> Watch -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> TimeoutSeconds -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> TimeoutSeconds -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> ResourceVersion -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> ResourceVersion -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> Pretty -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> Pretty -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> Limit -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> Limit -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> LabelSelector -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> LabelSelector -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> FieldSelector -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> FieldSelector -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> Continue -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> Continue -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> Limit -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> Limit -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> Continue -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> Continue -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteAPIService PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteAPIService contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteAPIService contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteAPIService contentType res accept Source # | |
HasOptionalParam DeleteAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteAPIService contentType res accept -> Pretty -> KubernetesRequest DeleteAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteAPIService contentType res accept -> Pretty -> KubernetesRequest DeleteAPIService contentType res accept Source # | |
HasOptionalParam DeleteAPIService OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteAPIService contentType res accept -> OrphanDependents -> KubernetesRequest DeleteAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteAPIService contentType res accept -> OrphanDependents -> KubernetesRequest DeleteAPIService contentType res accept Source # | |
HasOptionalParam DeleteAPIService GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteAPIService contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteAPIService contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteAPIService contentType res accept Source # | |
HasOptionalParam DeleteAPIService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteAPIService contentType res accept -> DryRun -> KubernetesRequest DeleteAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteAPIService contentType res accept -> DryRun -> KubernetesRequest DeleteAPIService contentType res accept Source # | |
HasOptionalParam CreateAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateAPIService contentType res accept -> Pretty -> KubernetesRequest CreateAPIService contentType res accept Source # (-&-) :: KubernetesRequest CreateAPIService contentType res accept -> Pretty -> KubernetesRequest CreateAPIService contentType res accept Source # | |
HasOptionalParam CreateAPIService FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateAPIService contentType res accept -> FieldManager -> KubernetesRequest CreateAPIService contentType res accept Source # (-&-) :: KubernetesRequest CreateAPIService contentType res accept -> FieldManager -> KubernetesRequest CreateAPIService contentType res accept Source # | |
HasOptionalParam CreateAPIService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateAPIService contentType res accept -> DryRun -> KubernetesRequest CreateAPIService contentType res accept Source # (-&-) :: KubernetesRequest CreateAPIService contentType res accept -> DryRun -> KubernetesRequest CreateAPIService contentType res accept Source # | |
HasOptionalParam ReplaceAPIServiceStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceAPIServiceStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAPIServiceStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceAPIServiceStatus contentType res accept Source # | |
HasOptionalParam ReplaceAPIServiceStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceAPIServiceStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAPIServiceStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceAPIServiceStatus contentType res accept Source # | |
HasOptionalParam ReplaceAPIServiceStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceAPIServiceStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAPIServiceStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceAPIServiceStatus contentType res accept Source # | |
HasOptionalParam ReplaceAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceAPIService contentType res accept -> Pretty -> KubernetesRequest ReplaceAPIService contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAPIService contentType res accept -> Pretty -> KubernetesRequest ReplaceAPIService contentType res accept Source # | |
HasOptionalParam ReplaceAPIService FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceAPIService contentType res accept -> FieldManager -> KubernetesRequest ReplaceAPIService contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAPIService contentType res accept -> FieldManager -> KubernetesRequest ReplaceAPIService contentType res accept Source # | |
HasOptionalParam ReplaceAPIService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceAPIService contentType res accept -> DryRun -> KubernetesRequest ReplaceAPIService contentType res accept Source # (-&-) :: KubernetesRequest ReplaceAPIService contentType res accept -> DryRun -> KubernetesRequest ReplaceAPIService contentType res accept Source # | |
HasOptionalParam ReadAPIServiceStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReadAPIServiceStatus contentType res accept -> Pretty -> KubernetesRequest ReadAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadAPIServiceStatus contentType res accept -> Pretty -> KubernetesRequest ReadAPIServiceStatus contentType res accept Source # | |
HasOptionalParam ReadAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReadAPIService contentType res accept -> Pretty -> KubernetesRequest ReadAPIService contentType res accept Source # (-&-) :: KubernetesRequest ReadAPIService contentType res accept -> Pretty -> KubernetesRequest ReadAPIService contentType res accept Source # | |
HasOptionalParam ReadAPIService Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReadAPIService contentType res accept -> Export -> KubernetesRequest ReadAPIService contentType res accept Source # (-&-) :: KubernetesRequest ReadAPIService contentType res accept -> Export -> KubernetesRequest ReadAPIService contentType res accept Source # | |
HasOptionalParam ReadAPIService Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReadAPIService contentType res accept -> Exact -> KubernetesRequest ReadAPIService contentType res accept Source # (-&-) :: KubernetesRequest ReadAPIService contentType res accept -> Exact -> KubernetesRequest ReadAPIService contentType res accept Source # | |
HasOptionalParam PatchAPIServiceStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> Pretty -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> Pretty -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # | |
HasOptionalParam PatchAPIServiceStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> Force -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> Force -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # | |
HasOptionalParam PatchAPIServiceStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> FieldManager -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> FieldManager -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # | |
HasOptionalParam PatchAPIServiceStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> DryRun -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIServiceStatus contentType res accept -> DryRun -> KubernetesRequest PatchAPIServiceStatus contentType res accept Source # | |
HasOptionalParam PatchAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchAPIService contentType res accept -> Pretty -> KubernetesRequest PatchAPIService contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIService contentType res accept -> Pretty -> KubernetesRequest PatchAPIService contentType res accept Source # | |
HasOptionalParam PatchAPIService Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchAPIService contentType res accept -> Force -> KubernetesRequest PatchAPIService contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIService contentType res accept -> Force -> KubernetesRequest PatchAPIService contentType res accept Source # | |
HasOptionalParam PatchAPIService FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchAPIService contentType res accept -> FieldManager -> KubernetesRequest PatchAPIService contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIService contentType res accept -> FieldManager -> KubernetesRequest PatchAPIService contentType res accept Source # | |
HasOptionalParam PatchAPIService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchAPIService contentType res accept -> DryRun -> KubernetesRequest PatchAPIService contentType res accept Source # (-&-) :: KubernetesRequest PatchAPIService contentType res accept -> DryRun -> KubernetesRequest PatchAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> Watch -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> Watch -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> TimeoutSeconds -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> TimeoutSeconds -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> ResourceVersion -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> ResourceVersion -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> Pretty -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> Pretty -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> Limit -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> Limit -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> LabelSelector -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> LabelSelector -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> FieldSelector -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> FieldSelector -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> Continue -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> Continue -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam ListAPIService AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListAPIService contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListAPIService contentType res accept Source # (-&-) :: KubernetesRequest ListAPIService contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> Limit -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> Limit -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteCollectionAPIService Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> Continue -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionAPIService contentType res accept -> Continue -> KubernetesRequest DeleteCollectionAPIService contentType res accept Source # | |
HasOptionalParam DeleteAPIService PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteAPIService contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteAPIService contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteAPIService contentType res accept Source # | |
HasOptionalParam DeleteAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteAPIService contentType res accept -> Pretty -> KubernetesRequest DeleteAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteAPIService contentType res accept -> Pretty -> KubernetesRequest DeleteAPIService contentType res accept Source # | |
HasOptionalParam DeleteAPIService OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteAPIService contentType res accept -> OrphanDependents -> KubernetesRequest DeleteAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteAPIService contentType res accept -> OrphanDependents -> KubernetesRequest DeleteAPIService contentType res accept Source # | |
HasOptionalParam DeleteAPIService GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteAPIService contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteAPIService contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteAPIService contentType res accept Source # | |
HasOptionalParam DeleteAPIService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteAPIService contentType res accept -> DryRun -> KubernetesRequest DeleteAPIService contentType res accept Source # (-&-) :: KubernetesRequest DeleteAPIService contentType res accept -> DryRun -> KubernetesRequest DeleteAPIService contentType res accept Source # | |
HasOptionalParam CreateAPIService Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest CreateAPIService contentType res accept -> Pretty -> KubernetesRequest CreateAPIService contentType res accept Source # (-&-) :: KubernetesRequest CreateAPIService contentType res accept -> Pretty -> KubernetesRequest CreateAPIService contentType res accept Source # | |
HasOptionalParam CreateAPIService FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest CreateAPIService contentType res accept -> FieldManager -> KubernetesRequest CreateAPIService contentType res accept Source # (-&-) :: KubernetesRequest CreateAPIService contentType res accept -> FieldManager -> KubernetesRequest CreateAPIService contentType res accept Source # | |
HasOptionalParam CreateAPIService DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiregistrationV1 Methods applyOptionalParam :: KubernetesRequest CreateAPIService contentType res accept -> DryRun -> KubernetesRequest CreateAPIService contentType res accept Source # (-&-) :: KubernetesRequest CreateAPIService contentType res accept -> DryRun -> KubernetesRequest CreateAPIService contentType res accept Source # | |
HasOptionalParam ReplaceCustomResourceDefinitionStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam ReplaceCustomResourceDefinitionStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam ReplaceCustomResourceDefinitionStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam ReplaceCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest ReplaceCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest ReplaceCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ReplaceCustomResourceDefinition FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCustomResourceDefinition contentType res accept -> FieldManager -> KubernetesRequest ReplaceCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCustomResourceDefinition contentType res accept -> FieldManager -> KubernetesRequest ReplaceCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ReplaceCustomResourceDefinition DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest ReplaceCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest ReplaceCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ReadCustomResourceDefinitionStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCustomResourceDefinitionStatus contentType res accept -> Pretty -> KubernetesRequest ReadCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadCustomResourceDefinitionStatus contentType res accept -> Pretty -> KubernetesRequest ReadCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam ReadCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest ReadCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ReadCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest ReadCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ReadCustomResourceDefinition Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCustomResourceDefinition contentType res accept -> Export -> KubernetesRequest ReadCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ReadCustomResourceDefinition contentType res accept -> Export -> KubernetesRequest ReadCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ReadCustomResourceDefinition Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadCustomResourceDefinition contentType res accept -> Exact -> KubernetesRequest ReadCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ReadCustomResourceDefinition contentType res accept -> Exact -> KubernetesRequest ReadCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinitionStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> Pretty -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> Pretty -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinitionStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> Force -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> Force -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinitionStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> FieldManager -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> FieldManager -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinitionStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> DryRun -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> DryRun -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinition Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> Force -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> Force -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinition FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> FieldManager -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> FieldManager -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinition DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Watch -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Watch -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> ResourceVersion -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> ResourceVersion -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Limit -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Limit -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> LabelSelector -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> LabelSelector -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> FieldSelector -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> FieldSelector -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Continue -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Continue -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCustomResourceDefinition PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCustomResourceDefinition OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCustomResourceDefinition GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCustomResourceDefinition DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> Limit -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> Limit -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> Continue -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> Continue -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam CreateCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest CreateCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest CreateCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest CreateCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam CreateCustomResourceDefinition FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateCustomResourceDefinition contentType res accept -> FieldManager -> KubernetesRequest CreateCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest CreateCustomResourceDefinition contentType res accept -> FieldManager -> KubernetesRequest CreateCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam CreateCustomResourceDefinition DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest CreateCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest CreateCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest CreateCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ReplaceCustomResourceDefinitionStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept -> Pretty -> KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam ReplaceCustomResourceDefinitionStatus FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept -> FieldManager -> KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam ReplaceCustomResourceDefinitionStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept -> DryRun -> KubernetesRequest ReplaceCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam ReplaceCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest ReplaceCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest ReplaceCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ReplaceCustomResourceDefinition FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceCustomResourceDefinition contentType res accept -> FieldManager -> KubernetesRequest ReplaceCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCustomResourceDefinition contentType res accept -> FieldManager -> KubernetesRequest ReplaceCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ReplaceCustomResourceDefinition DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ReplaceCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest ReplaceCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ReplaceCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest ReplaceCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ReadCustomResourceDefinitionStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ReadCustomResourceDefinitionStatus contentType res accept -> Pretty -> KubernetesRequest ReadCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest ReadCustomResourceDefinitionStatus contentType res accept -> Pretty -> KubernetesRequest ReadCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam ReadCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ReadCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest ReadCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ReadCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest ReadCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ReadCustomResourceDefinition Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ReadCustomResourceDefinition contentType res accept -> Export -> KubernetesRequest ReadCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ReadCustomResourceDefinition contentType res accept -> Export -> KubernetesRequest ReadCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ReadCustomResourceDefinition Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ReadCustomResourceDefinition contentType res accept -> Exact -> KubernetesRequest ReadCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ReadCustomResourceDefinition contentType res accept -> Exact -> KubernetesRequest ReadCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinitionStatus Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> Pretty -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> Pretty -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinitionStatus Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> Force -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> Force -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinitionStatus FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> FieldManager -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> FieldManager -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinitionStatus DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> DryRun -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept -> DryRun -> KubernetesRequest PatchCustomResourceDefinitionStatus contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinition Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> Force -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> Force -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinition FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> FieldManager -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> FieldManager -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam PatchCustomResourceDefinition DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest PatchCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest PatchCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Watch -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Watch -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> TimeoutSeconds -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> ResourceVersion -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> ResourceVersion -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Limit -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Limit -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> LabelSelector -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> LabelSelector -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> FieldSelector -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> FieldSelector -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Continue -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> Continue -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ListCustomResourceDefinition AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest ListCustomResourceDefinition contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCustomResourceDefinition PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCustomResourceDefinition OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCustomResourceDefinition GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCustomResourceDefinition DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest DeleteCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> Limit -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> Limit -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam DeleteCollectionCustomResourceDefinition Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> Continue -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept -> Continue -> KubernetesRequest DeleteCollectionCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam CreateCustomResourceDefinition Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest CreateCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest CreateCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest CreateCustomResourceDefinition contentType res accept -> Pretty -> KubernetesRequest CreateCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam CreateCustomResourceDefinition FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest CreateCustomResourceDefinition contentType res accept -> FieldManager -> KubernetesRequest CreateCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest CreateCustomResourceDefinition contentType res accept -> FieldManager -> KubernetesRequest CreateCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam CreateCustomResourceDefinition DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.ApiextensionsV1 Methods applyOptionalParam :: KubernetesRequest CreateCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest CreateCustomResourceDefinition contentType res accept Source # (-&-) :: KubernetesRequest CreateCustomResourceDefinition contentType res accept -> DryRun -> KubernetesRequest CreateCustomResourceDefinition contentType res accept Source # | |
HasOptionalParam ReplaceValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReplaceValidatingWebhookConfiguration FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReplaceValidatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReplaceMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReplaceMutatingWebhookConfiguration FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReplaceMutatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReadValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReadValidatingWebhookConfiguration Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept -> Export -> KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept -> Export -> KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReadValidatingWebhookConfiguration Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept -> Exact -> KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept -> Exact -> KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReadMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReadMutatingWebhookConfiguration Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept -> Export -> KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept -> Export -> KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReadMutatingWebhookConfiguration Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept -> Exact -> KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept -> Exact -> KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchValidatingWebhookConfiguration Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> Force -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> Force -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchValidatingWebhookConfiguration FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchValidatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchMutatingWebhookConfiguration Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> Force -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> Force -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchMutatingWebhookConfiguration FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchMutatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Watch -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Watch -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Watch -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Watch -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteValidatingWebhookConfiguration PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteValidatingWebhookConfiguration OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteValidatingWebhookConfiguration GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteValidatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteMutatingWebhookConfiguration PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteMutatingWebhookConfiguration OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteMutatingWebhookConfiguration GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteMutatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam CreateValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam CreateValidatingWebhookConfiguration FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam CreateValidatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam CreateMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam CreateMutatingWebhookConfiguration FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam CreateMutatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1beta1 Methods applyOptionalParam :: KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReplaceValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReplaceValidatingWebhookConfiguration FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReplaceValidatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest ReplaceValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReplaceMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReplaceMutatingWebhookConfiguration FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReplaceMutatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest ReplaceMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReadValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReadValidatingWebhookConfiguration Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept -> Export -> KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept -> Export -> KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReadValidatingWebhookConfiguration Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept -> Exact -> KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept -> Exact -> KubernetesRequest ReadValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReadMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReadMutatingWebhookConfiguration Export Source # | Optional Param "export" - Should this value be exported. Export strips fields that a user can not specify. Deprecated. Planned for removal in 1.18. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept -> Export -> KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept -> Export -> KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ReadMutatingWebhookConfiguration Exact Source # | Optional Param "exact" - Should the export be exact. Exact export maintains cluster-specific fields like |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept -> Exact -> KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept -> Exact -> KubernetesRequest ReadMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchValidatingWebhookConfiguration Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> Force -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> Force -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchValidatingWebhookConfiguration FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchValidatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest PatchValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchMutatingWebhookConfiguration Force Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> Force -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> Force -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchMutatingWebhookConfiguration FieldManager Source # | 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). |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam PatchMutatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest PatchMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Watch -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Watch -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListValidatingWebhookConfiguration AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListValidatingWebhookConfiguration contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration Watch Source # | Optional Param "watch" - Watch for changes to the described resources and return them as a stream of add, update, and remove notifications. Specify resourceVersion. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Watch -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Watch -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam ListMutatingWebhookConfiguration AllowWatchBookmarks Source # | 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. If the feature gate WatchBookmarks is not enabled in apiserver, this field is ignored. This field is beta. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest ListMutatingWebhookConfiguration contentType res accept -> AllowWatchBookmarks -> KubernetesRequest ListMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteValidatingWebhookConfiguration PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteValidatingWebhookConfiguration OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteValidatingWebhookConfiguration GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteValidatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteMutatingWebhookConfiguration PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteMutatingWebhookConfiguration OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteMutatingWebhookConfiguration GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteMutatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionValidatingWebhookConfiguration Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest DeleteCollectionValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration TimeoutSeconds Source # | Optional Param "timeoutSeconds" - Timeout for the list/watch call. This limits the duration of the call, regardless of any activity or inactivity. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> TimeoutSeconds -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration ResourceVersion Source # | Optional Param "resourceVersion" - When specified with a watch call, shows changes that occur after that particular version of a resource. Defaults to changes from the beginning of history. When specified for list: - if unset, then the result is returned from remote storage based on quorum-read flag; - if it's 0, then we simply return what we currently have in cache, no guarantee; - if set to non zero, then the result is at least as fresh as given rv. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> ResourceVersion -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration PropagationPolicy Source # | 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: |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> PropagationPolicy -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration OrphanDependents Source # | Optional Param "orphanDependents" - Deprecated: please use the PropagationPolicy, this field will be deprecated in 1.7. Should the dependent objects be orphaned. If truefalse, the "orphan" finalizer will be added toremoved from the object's finalizers list. Either this field or PropagationPolicy may be set, but not both. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> OrphanDependents -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration Limit Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> Limit -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration LabelSelector Source # | Optional Param "labelSelector" - A selector to restrict the list of returned objects by their labels. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> LabelSelector -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration GracePeriodSeconds Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> GracePeriodSeconds -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration FieldSelector Source # | Optional Param "fieldSelector" - A selector to restrict the list of returned objects by their fields. Defaults to everything. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> FieldSelector -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam DeleteCollectionMutatingWebhookConfiguration Continue Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept -> Continue -> KubernetesRequest DeleteCollectionMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam CreateValidatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam CreateValidatingWebhookConfiguration FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam CreateValidatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest CreateValidatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam CreateMutatingWebhookConfiguration Pretty Source # | Optional Param "pretty" - If |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept -> Pretty -> KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam CreateMutatingWebhookConfiguration FieldManager Source # | 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. |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept -> FieldManager -> KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept Source # | |
HasOptionalParam CreateMutatingWebhookConfiguration DryRun Source # | 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 |
Defined in Kubernetes.OpenAPI.API.AdmissionregistrationV1 Methods applyOptionalParam :: KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept Source # (-&-) :: KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept -> DryRun -> KubernetesRequest CreateMutatingWebhookConfiguration contentType res accept Source # |
Request Params
Constructors
Params | |
Fields |
paramsQueryL :: Lens_' Params Query Source #
paramsQuery
Lens
paramsBodyL :: Lens_' Params ParamBody Source #
paramsBody
Lens
Request Body
KubernetesRequest Utils
Arguments
:: Method | Method |
-> [ByteString] | Endpoint |
-> KubernetesRequest req contentType res accept | req: Request Type, res: Response Type |
setHeader :: KubernetesRequest req contentType res accept -> [Header] -> KubernetesRequest req contentType res accept Source #
addHeader :: KubernetesRequest req contentType res accept -> [Header] -> KubernetesRequest req contentType res accept Source #
removeHeader :: KubernetesRequest req contentType res accept -> [HeaderName] -> KubernetesRequest req contentType res accept Source #
_setContentTypeHeader :: forall req contentType res accept. MimeType contentType => KubernetesRequest req contentType res accept -> KubernetesRequest req contentType res accept Source #
_setAcceptHeader :: forall req contentType res accept. MimeType accept => KubernetesRequest req contentType res accept -> KubernetesRequest req contentType res accept Source #
setQuery :: KubernetesRequest req contentType res accept -> [QueryItem] -> KubernetesRequest req contentType res accept Source #
addQuery :: KubernetesRequest req contentType res accept -> [QueryItem] -> KubernetesRequest req contentType res accept Source #
addForm :: KubernetesRequest req contentType res accept -> Form -> KubernetesRequest req contentType res accept Source #
_addMultiFormPart :: KubernetesRequest req contentType res accept -> Part -> KubernetesRequest req contentType res accept Source #
_setBodyBS :: KubernetesRequest req contentType res accept -> ByteString -> KubernetesRequest req contentType res accept Source #
_setBodyLBS :: KubernetesRequest req contentType res accept -> ByteString -> KubernetesRequest req contentType res accept Source #
_hasAuthType :: AuthMethod authMethod => KubernetesRequest req contentType res accept -> Proxy authMethod -> KubernetesRequest req contentType res accept Source #
Params Utils
toPath :: ToHttpApiData a => a -> ByteString Source #
toHeader :: ToHttpApiData a => (HeaderName, a) -> [Header] Source #
toForm :: ToHttpApiData v => (ByteString, v) -> Form Source #
toQuery :: ToHttpApiData a => (ByteString, Maybe a) -> [QueryItem] Source #
OpenAPI CollectionFormat
Utils
data CollectionFormat Source #
Determines the format of the array if type array is used.
Constructors
CommaSeparated | CSV format for multiple parameters. |
SpaceSeparated | Also called SSV |
TabSeparated | Also called TSV |
PipeSeparated | `value1|value2|value2` |
MultiParamArray | Using multiple GET parameters, e.g. `foo=bar&foo=baz`. This is valid only for parameters in "query" ( |
toHeaderColl :: ToHttpApiData a => CollectionFormat -> (HeaderName, [a]) -> [Header] Source #
toFormColl :: ToHttpApiData v => CollectionFormat -> (ByteString, [v]) -> Form Source #
toQueryColl :: ToHttpApiData a => CollectionFormat -> (ByteString, Maybe [a]) -> Query Source #
_toColl :: Traversable f => CollectionFormat -> (f a -> [(b, ByteString)]) -> f [a] -> [(b, ByteString)] Source #
_toCollA :: (Traversable f, Traversable t, Alternative t) => CollectionFormat -> (f (t a) -> [(b, t ByteString)]) -> f (t [a]) -> [(b, t ByteString)] Source #
_toCollA' :: (Monoid c, Traversable f, Traversable t, Alternative t) => CollectionFormat -> (f (t a) -> [(b, t c)]) -> (Char -> c) -> f (t [a]) -> [(b, t c)] Source #
AuthMethods
class Typeable a => AuthMethod a where Source #
Provides a method to apply auth methods to requests
Methods
applyAuthMethod :: KubernetesClientConfig -> a -> KubernetesRequest req contentType res accept -> IO (KubernetesRequest req contentType res accept) Source #
Instances
AuthMethod AnyAuthMethod Source # | |
Defined in Kubernetes.OpenAPI.Core Methods applyAuthMethod :: KubernetesClientConfig -> AnyAuthMethod -> KubernetesRequest req contentType res accept -> IO (KubernetesRequest req contentType res accept) Source # | |
AuthMethod AuthApiKeyBearerToken Source # | |
Defined in Kubernetes.OpenAPI.Model Methods applyAuthMethod :: KubernetesClientConfig -> AuthApiKeyBearerToken -> KubernetesRequest req contentType res accept -> IO (KubernetesRequest req contentType res accept) Source # |
data AnyAuthMethod Source #
An existential wrapper for any AuthMethod
Constructors
forall a.AuthMethod a => AnyAuthMethod a |
Instances
AuthMethod AnyAuthMethod Source # | |
Defined in Kubernetes.OpenAPI.Core Methods applyAuthMethod :: KubernetesClientConfig -> AnyAuthMethod -> KubernetesRequest req contentType res accept -> IO (KubernetesRequest req contentType res accept) Source # |
data AuthMethodException Source #
indicates exceptions related to AuthMethods
Constructors
AuthMethodException String |
Instances
Show AuthMethodException Source # | |
Defined in Kubernetes.OpenAPI.Core Methods showsPrec :: Int -> AuthMethodException -> ShowS # show :: AuthMethodException -> String # showList :: [AuthMethodException] -> ShowS # | |
Exception AuthMethodException Source # | |
Defined in Kubernetes.OpenAPI.Core Methods toException :: AuthMethodException -> SomeException # fromException :: SomeException -> Maybe AuthMethodException # |
_applyAuthMethods :: KubernetesRequest req contentType res accept -> KubernetesClientConfig -> IO (KubernetesRequest req contentType res accept) Source #
apply all matching AuthMethods in config to request
Utils
_omitNulls :: [(Text, Value)] -> Value Source #
Removes Null fields. (OpenAPI-Specification 2.0 does not allow Null in JSON)
_toFormItem :: (ToHttpApiData a, Functor f) => t -> f a -> f (t, [Text]) Source #
Encodes fields using WH.toQueryParam
_memptyToNothing :: (Monoid a, Eq a) => Maybe a -> Maybe a Source #
Collapse (Just mempty) to Nothing
DateTime Formatting
Constructors
DateTime | |
Fields |
Instances
_readDateTime :: MonadFail m => String -> m DateTime Source #
TI.parseTimeM True TI.defaultTimeLocale "%FT%T%QZ"
_showDateTime :: FormatTime t => t -> String Source #
TI.formatTime TI.defaultTimeLocale "%FT%T%6QZ"
_parseISO8601 :: (ParseTime t, MonadFail m, Alternative m) => String -> m t Source #
parse an ISO8601 date-time string
Date Formatting
Instances
Enum Date Source # | |
Eq Date Source # | |
Data Date Source # | |
Defined in Kubernetes.OpenAPI.Core Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Date -> c Date # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Date # dataTypeOf :: Date -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Date) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Date) # gmapT :: (forall b. Data b => b -> b) -> Date -> Date # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r # gmapQ :: (forall d. Data d => d -> u) -> Date -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Date -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Date -> m Date # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Date -> m Date # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Date -> m Date # | |
Ord Date Source # | |
Show Date Source # | |
Ix Date Source # | |
ToJSON Date Source # | |
Defined in Kubernetes.OpenAPI.Core | |
FromJSON Date Source # | |
NFData Date Source # | |
Defined in Kubernetes.OpenAPI.Core | |
ToHttpApiData Date Source # | |
Defined in Kubernetes.OpenAPI.Core Methods toUrlPiece :: Date -> Text # toEncodedUrlPiece :: Date -> Builder # toHeader :: Date -> ByteString # toQueryParam :: Date -> Text # | |
FromHttpApiData Date Source # | |
Defined in Kubernetes.OpenAPI.Core | |
MimeRender MimeMultipartFormData Date Source # | |
Defined in Kubernetes.OpenAPI.Core Methods mimeRender :: Proxy MimeMultipartFormData -> Date -> ByteString Source # mimeRender' :: MimeMultipartFormData -> Date -> ByteString Source # |
_readDate :: MonadFail m => String -> m Date Source #
TI.parseTimeM True TI.defaultTimeLocale "%Y-%m-%d"
_showDate :: FormatTime t => t -> String Source #
TI.formatTime TI.defaultTimeLocale "%Y-%m-%d"
Byte/Binary Formatting
base64 encoded characters
Constructors
ByteArray | |
Fields |
Instances
_showByteArray :: ByteArray -> Text Source #
show base64 encoded characters
any sequence of octets
Constructors
Binary | |
Fields |
Instances
_showBinaryBase64 :: Binary -> Text Source #