{-
   Kubernetes

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

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

{-|
Module : Kubernetes.OpenAPI.Model
-}

{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-unused-matches -fno-warn-unused-binds -fno-warn-unused-imports #-}

module Kubernetes.OpenAPI.Model (module Kubernetes.OpenAPI.Model, module Kubernetes.OpenAPI.ImportMappings) where

import Kubernetes.OpenAPI.Core
import Kubernetes.OpenAPI.MimeTypes
import Kubernetes.OpenAPI.ImportMappings

import Data.Aeson ((.:),(.:!),(.:?),(.=))

import qualified Control.Arrow as P (left)
import qualified Data.Aeson as A
import qualified Data.ByteString as B
import qualified Data.ByteString.Base64 as B64
import qualified Data.ByteString.Char8 as BC
import qualified Data.ByteString.Lazy as BL
import qualified Data.Data as P (Typeable, TypeRep, typeOf, typeRep)
import qualified Data.Foldable as P
import qualified Data.HashMap.Lazy as HM
import qualified Data.Map as Map
import qualified Data.Maybe as P
import qualified Data.Set as Set
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Time as TI
import qualified Lens.Micro as L
import qualified Web.FormUrlEncoded as WH
import qualified Web.HttpApiData as WH

import Control.Applicative ((<|>))
import Control.Applicative (Alternative)
import Data.Function ((&))
import Data.Monoid ((<>))
import Data.Text (Text)
import Prelude (($),(/=),(.),(<$>),(<*>),(>>=),(=<<),Maybe(..),Bool(..),Char,Double,FilePath,Float,Int,Integer,String,fmap,undefined,mempty,maybe,pure,Monad,Applicative,Functor)

import qualified Prelude as P



-- * Parameter newtypes


-- ** AllowWatchBookmarks
newtype AllowWatchBookmarks = AllowWatchBookmarks { unAllowWatchBookmarks :: Bool } deriving (P.Eq, P.Show)

-- ** Body
newtype Body = Body { unBody :: A.Value } deriving (P.Eq, P.Show, A.ToJSON)

-- ** Command
newtype Command = Command { unCommand :: Text } deriving (P.Eq, P.Show)

-- ** Container
newtype Container = Container { unContainer :: Text } deriving (P.Eq, P.Show)

-- ** Continue
newtype Continue = Continue { unContinue :: Text } deriving (P.Eq, P.Show)

-- ** DryRun
newtype DryRun = DryRun { unDryRun :: Text } deriving (P.Eq, P.Show)

-- ** Exact
newtype Exact = Exact { unExact :: Bool } deriving (P.Eq, P.Show)

-- ** Export
newtype Export = Export { unExport :: Bool } deriving (P.Eq, P.Show)

-- ** FieldManager
newtype FieldManager = FieldManager { unFieldManager :: Text } deriving (P.Eq, P.Show)

-- ** FieldSelector
newtype FieldSelector = FieldSelector { unFieldSelector :: Text } deriving (P.Eq, P.Show)

-- ** Follow
newtype Follow = Follow { unFollow :: Bool } deriving (P.Eq, P.Show)

-- ** Force
newtype Force = Force { unForce :: Bool } deriving (P.Eq, P.Show)

-- ** GracePeriodSeconds
newtype GracePeriodSeconds = GracePeriodSeconds { unGracePeriodSeconds :: Int } deriving (P.Eq, P.Show)

-- ** Group
newtype Group = Group { unGroup :: Text } deriving (P.Eq, P.Show)

-- ** LabelSelector
newtype LabelSelector = LabelSelector { unLabelSelector :: Text } deriving (P.Eq, P.Show)

-- ** Limit
newtype Limit = Limit { unLimit :: Int } deriving (P.Eq, P.Show)

-- ** LimitBytes
newtype LimitBytes = LimitBytes { unLimitBytes :: Int } deriving (P.Eq, P.Show)

-- ** Logpath
newtype Logpath = Logpath { unLogpath :: Text } deriving (P.Eq, P.Show)

-- ** Name
newtype Name = Name { unName :: Text } deriving (P.Eq, P.Show)

-- ** Namespace
newtype Namespace = Namespace { unNamespace :: Text } deriving (P.Eq, P.Show)

-- ** OrphanDependents
newtype OrphanDependents = OrphanDependents { unOrphanDependents :: Bool } deriving (P.Eq, P.Show)

-- ** Path
newtype Path = Path { unPath :: Text } deriving (P.Eq, P.Show)

-- ** Path2
newtype Path2 = Path2 { unPath2 :: Text } deriving (P.Eq, P.Show)

-- ** Plural
newtype Plural = Plural { unPlural :: Text } deriving (P.Eq, P.Show)

-- ** Ports
newtype Ports = Ports { unPorts :: Int } deriving (P.Eq, P.Show)

-- ** Pretty
newtype Pretty = Pretty { unPretty :: Text } deriving (P.Eq, P.Show)

-- ** Previous
newtype Previous = Previous { unPrevious :: Bool } deriving (P.Eq, P.Show)

-- ** PropagationPolicy
newtype PropagationPolicy = PropagationPolicy { unPropagationPolicy :: Text } deriving (P.Eq, P.Show)

-- ** ResourceVersion
newtype ResourceVersion = ResourceVersion { unResourceVersion :: Text } deriving (P.Eq, P.Show)

-- ** SinceSeconds
newtype SinceSeconds = SinceSeconds { unSinceSeconds :: Int } deriving (P.Eq, P.Show)

-- ** Stderr
newtype Stderr = Stderr { unStderr :: Bool } deriving (P.Eq, P.Show)

-- ** Stdin
newtype Stdin = Stdin { unStdin :: Bool } deriving (P.Eq, P.Show)

-- ** Stdout
newtype Stdout = Stdout { unStdout :: Bool } deriving (P.Eq, P.Show)

-- ** TailLines
newtype TailLines = TailLines { unTailLines :: Int } deriving (P.Eq, P.Show)

-- ** TimeoutSeconds
newtype TimeoutSeconds = TimeoutSeconds { unTimeoutSeconds :: Int } deriving (P.Eq, P.Show)

-- ** Timestamps
newtype Timestamps = Timestamps { unTimestamps :: Bool } deriving (P.Eq, P.Show)

-- ** Tty
newtype Tty = Tty { unTty :: Bool } deriving (P.Eq, P.Show)

-- ** Version
newtype Version = Version { unVersion :: Text } deriving (P.Eq, P.Show)

-- ** Watch
newtype Watch = Watch { unWatch :: Bool } deriving (P.Eq, P.Show)

-- * Models


-- ** AdmissionregistrationV1ServiceReference
-- | AdmissionregistrationV1ServiceReference
-- ServiceReference holds a reference to Service.legacy.k8s.io
data AdmissionregistrationV1ServiceReference = AdmissionregistrationV1ServiceReference
  { admissionregistrationV1ServiceReferenceName :: !(Text) -- ^ /Required/ "name" - &#x60;name&#x60; is the name of the service. Required
  , admissionregistrationV1ServiceReferenceNamespace :: !(Text) -- ^ /Required/ "namespace" - &#x60;namespace&#x60; is the namespace of the service. Required
  , admissionregistrationV1ServiceReferencePath :: !(Maybe Text) -- ^ "path" - &#x60;path&#x60; is an optional URL path which will be sent in any request to this service.
  , admissionregistrationV1ServiceReferencePort :: !(Maybe Int) -- ^ "port" - If specified, the port on the service that hosting webhook. Default to 443 for backward compatibility. &#x60;port&#x60; should be a valid port number (1-65535, inclusive).
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AdmissionregistrationV1ServiceReference
instance A.FromJSON AdmissionregistrationV1ServiceReference where
  parseJSON = A.withObject "AdmissionregistrationV1ServiceReference" $ \o ->
    AdmissionregistrationV1ServiceReference
      <$> (o .:  "name")
      <*> (o .:  "namespace")
      <*> (o .:? "path")
      <*> (o .:? "port")

-- | ToJSON AdmissionregistrationV1ServiceReference
instance A.ToJSON AdmissionregistrationV1ServiceReference where
  toJSON AdmissionregistrationV1ServiceReference {..} =
   _omitNulls
      [ "name" .= admissionregistrationV1ServiceReferenceName
      , "namespace" .= admissionregistrationV1ServiceReferenceNamespace
      , "path" .= admissionregistrationV1ServiceReferencePath
      , "port" .= admissionregistrationV1ServiceReferencePort
      ]


-- | Construct a value of type 'AdmissionregistrationV1ServiceReference' (by applying it's required fields, if any)
mkAdmissionregistrationV1ServiceReference
  :: Text -- ^ 'admissionregistrationV1ServiceReferenceName': `name` is the name of the service. Required
  -> Text -- ^ 'admissionregistrationV1ServiceReferenceNamespace': `namespace` is the namespace of the service. Required
  -> AdmissionregistrationV1ServiceReference
mkAdmissionregistrationV1ServiceReference admissionregistrationV1ServiceReferenceName admissionregistrationV1ServiceReferenceNamespace =
  AdmissionregistrationV1ServiceReference
  { admissionregistrationV1ServiceReferenceName
  , admissionregistrationV1ServiceReferenceNamespace
  , admissionregistrationV1ServiceReferencePath = Nothing
  , admissionregistrationV1ServiceReferencePort = Nothing
  }

-- ** AdmissionregistrationV1WebhookClientConfig
-- | AdmissionregistrationV1WebhookClientConfig
-- WebhookClientConfig contains the information to make a TLS connection with the webhook
data AdmissionregistrationV1WebhookClientConfig = AdmissionregistrationV1WebhookClientConfig
  { admissionregistrationV1WebhookClientConfigCaBundle :: !(Maybe ByteArray) -- ^ "caBundle" - &#x60;caBundle&#x60; is a PEM encoded CA bundle which will be used to validate the webhook&#39;s server certificate. If unspecified, system trust roots on the apiserver are used.
  , admissionregistrationV1WebhookClientConfigService :: !(Maybe AdmissionregistrationV1ServiceReference) -- ^ "service"
  , admissionregistrationV1WebhookClientConfigUrl :: !(Maybe Text) -- ^ "url" - &#x60;url&#x60; gives the location of the webhook, in standard URL form (&#x60;scheme://host:port/path&#x60;). Exactly one of &#x60;url&#x60; or &#x60;service&#x60; must be specified.  The &#x60;host&#x60; should not refer to a service running in the cluster; use the &#x60;service&#x60; field instead. The host might be resolved via external DNS in some apiservers (e.g., &#x60;kube-apiserver&#x60; cannot resolve in-cluster DNS as that would be a layering violation). &#x60;host&#x60; may also be an IP address.  Please note that using &#x60;localhost&#x60; or &#x60;127.0.0.1&#x60; as a &#x60;host&#x60; is risky unless you take great care to run this webhook on all hosts which run an apiserver which might need to make calls to this webhook. Such installs are likely to be non-portable, i.e., not easy to turn up in a new cluster.  The scheme must be \&quot;https\&quot;; the URL must begin with \&quot;https://\&quot;.  A path is optional, and if present may be any string permissible in a URL. You may use the path to pass an arbitrary string to the webhook, for example, a cluster identifier.  Attempting to use a user or basic auth e.g. \&quot;user:password@\&quot; is not allowed. Fragments (\&quot;#...\&quot;) and query parameters (\&quot;?...\&quot;) are not allowed, either.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AdmissionregistrationV1WebhookClientConfig
instance A.FromJSON AdmissionregistrationV1WebhookClientConfig where
  parseJSON = A.withObject "AdmissionregistrationV1WebhookClientConfig" $ \o ->
    AdmissionregistrationV1WebhookClientConfig
      <$> (o .:? "caBundle")
      <*> (o .:? "service")
      <*> (o .:? "url")

-- | ToJSON AdmissionregistrationV1WebhookClientConfig
instance A.ToJSON AdmissionregistrationV1WebhookClientConfig where
  toJSON AdmissionregistrationV1WebhookClientConfig {..} =
   _omitNulls
      [ "caBundle" .= admissionregistrationV1WebhookClientConfigCaBundle
      , "service" .= admissionregistrationV1WebhookClientConfigService
      , "url" .= admissionregistrationV1WebhookClientConfigUrl
      ]


-- | Construct a value of type 'AdmissionregistrationV1WebhookClientConfig' (by applying it's required fields, if any)
mkAdmissionregistrationV1WebhookClientConfig
  :: AdmissionregistrationV1WebhookClientConfig
mkAdmissionregistrationV1WebhookClientConfig =
  AdmissionregistrationV1WebhookClientConfig
  { admissionregistrationV1WebhookClientConfigCaBundle = Nothing
  , admissionregistrationV1WebhookClientConfigService = Nothing
  , admissionregistrationV1WebhookClientConfigUrl = Nothing
  }

-- ** AdmissionregistrationV1beta1ServiceReference
-- | AdmissionregistrationV1beta1ServiceReference
-- ServiceReference holds a reference to Service.legacy.k8s.io
data AdmissionregistrationV1beta1ServiceReference = AdmissionregistrationV1beta1ServiceReference
  { admissionregistrationV1beta1ServiceReferenceName :: !(Text) -- ^ /Required/ "name" - &#x60;name&#x60; is the name of the service. Required
  , admissionregistrationV1beta1ServiceReferenceNamespace :: !(Text) -- ^ /Required/ "namespace" - &#x60;namespace&#x60; is the namespace of the service. Required
  , admissionregistrationV1beta1ServiceReferencePath :: !(Maybe Text) -- ^ "path" - &#x60;path&#x60; is an optional URL path which will be sent in any request to this service.
  , admissionregistrationV1beta1ServiceReferencePort :: !(Maybe Int) -- ^ "port" - If specified, the port on the service that hosting webhook. Default to 443 for backward compatibility. &#x60;port&#x60; should be a valid port number (1-65535, inclusive).
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AdmissionregistrationV1beta1ServiceReference
instance A.FromJSON AdmissionregistrationV1beta1ServiceReference where
  parseJSON = A.withObject "AdmissionregistrationV1beta1ServiceReference" $ \o ->
    AdmissionregistrationV1beta1ServiceReference
      <$> (o .:  "name")
      <*> (o .:  "namespace")
      <*> (o .:? "path")
      <*> (o .:? "port")

-- | ToJSON AdmissionregistrationV1beta1ServiceReference
instance A.ToJSON AdmissionregistrationV1beta1ServiceReference where
  toJSON AdmissionregistrationV1beta1ServiceReference {..} =
   _omitNulls
      [ "name" .= admissionregistrationV1beta1ServiceReferenceName
      , "namespace" .= admissionregistrationV1beta1ServiceReferenceNamespace
      , "path" .= admissionregistrationV1beta1ServiceReferencePath
      , "port" .= admissionregistrationV1beta1ServiceReferencePort
      ]


-- | Construct a value of type 'AdmissionregistrationV1beta1ServiceReference' (by applying it's required fields, if any)
mkAdmissionregistrationV1beta1ServiceReference
  :: Text -- ^ 'admissionregistrationV1beta1ServiceReferenceName': `name` is the name of the service. Required
  -> Text -- ^ 'admissionregistrationV1beta1ServiceReferenceNamespace': `namespace` is the namespace of the service. Required
  -> AdmissionregistrationV1beta1ServiceReference
mkAdmissionregistrationV1beta1ServiceReference admissionregistrationV1beta1ServiceReferenceName admissionregistrationV1beta1ServiceReferenceNamespace =
  AdmissionregistrationV1beta1ServiceReference
  { admissionregistrationV1beta1ServiceReferenceName
  , admissionregistrationV1beta1ServiceReferenceNamespace
  , admissionregistrationV1beta1ServiceReferencePath = Nothing
  , admissionregistrationV1beta1ServiceReferencePort = Nothing
  }

-- ** AdmissionregistrationV1beta1WebhookClientConfig
-- | AdmissionregistrationV1beta1WebhookClientConfig
-- WebhookClientConfig contains the information to make a TLS connection with the webhook
data AdmissionregistrationV1beta1WebhookClientConfig = AdmissionregistrationV1beta1WebhookClientConfig
  { admissionregistrationV1beta1WebhookClientConfigCaBundle :: !(Maybe ByteArray) -- ^ "caBundle" - &#x60;caBundle&#x60; is a PEM encoded CA bundle which will be used to validate the webhook&#39;s server certificate. If unspecified, system trust roots on the apiserver are used.
  , admissionregistrationV1beta1WebhookClientConfigService :: !(Maybe AdmissionregistrationV1beta1ServiceReference) -- ^ "service"
  , admissionregistrationV1beta1WebhookClientConfigUrl :: !(Maybe Text) -- ^ "url" - &#x60;url&#x60; gives the location of the webhook, in standard URL form (&#x60;scheme://host:port/path&#x60;). Exactly one of &#x60;url&#x60; or &#x60;service&#x60; must be specified.  The &#x60;host&#x60; should not refer to a service running in the cluster; use the &#x60;service&#x60; field instead. The host might be resolved via external DNS in some apiservers (e.g., &#x60;kube-apiserver&#x60; cannot resolve in-cluster DNS as that would be a layering violation). &#x60;host&#x60; may also be an IP address.  Please note that using &#x60;localhost&#x60; or &#x60;127.0.0.1&#x60; as a &#x60;host&#x60; is risky unless you take great care to run this webhook on all hosts which run an apiserver which might need to make calls to this webhook. Such installs are likely to be non-portable, i.e., not easy to turn up in a new cluster.  The scheme must be \&quot;https\&quot;; the URL must begin with \&quot;https://\&quot;.  A path is optional, and if present may be any string permissible in a URL. You may use the path to pass an arbitrary string to the webhook, for example, a cluster identifier.  Attempting to use a user or basic auth e.g. \&quot;user:password@\&quot; is not allowed. Fragments (\&quot;#...\&quot;) and query parameters (\&quot;?...\&quot;) are not allowed, either.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AdmissionregistrationV1beta1WebhookClientConfig
instance A.FromJSON AdmissionregistrationV1beta1WebhookClientConfig where
  parseJSON = A.withObject "AdmissionregistrationV1beta1WebhookClientConfig" $ \o ->
    AdmissionregistrationV1beta1WebhookClientConfig
      <$> (o .:? "caBundle")
      <*> (o .:? "service")
      <*> (o .:? "url")

-- | ToJSON AdmissionregistrationV1beta1WebhookClientConfig
instance A.ToJSON AdmissionregistrationV1beta1WebhookClientConfig where
  toJSON AdmissionregistrationV1beta1WebhookClientConfig {..} =
   _omitNulls
      [ "caBundle" .= admissionregistrationV1beta1WebhookClientConfigCaBundle
      , "service" .= admissionregistrationV1beta1WebhookClientConfigService
      , "url" .= admissionregistrationV1beta1WebhookClientConfigUrl
      ]


-- | Construct a value of type 'AdmissionregistrationV1beta1WebhookClientConfig' (by applying it's required fields, if any)
mkAdmissionregistrationV1beta1WebhookClientConfig
  :: AdmissionregistrationV1beta1WebhookClientConfig
mkAdmissionregistrationV1beta1WebhookClientConfig =
  AdmissionregistrationV1beta1WebhookClientConfig
  { admissionregistrationV1beta1WebhookClientConfigCaBundle = Nothing
  , admissionregistrationV1beta1WebhookClientConfigService = Nothing
  , admissionregistrationV1beta1WebhookClientConfigUrl = Nothing
  }

-- ** ApiextensionsV1ServiceReference
-- | ApiextensionsV1ServiceReference
-- ServiceReference holds a reference to Service.legacy.k8s.io
data ApiextensionsV1ServiceReference = ApiextensionsV1ServiceReference
  { apiextensionsV1ServiceReferenceName :: !(Text) -- ^ /Required/ "name" - name is the name of the service. Required
  , apiextensionsV1ServiceReferenceNamespace :: !(Text) -- ^ /Required/ "namespace" - namespace is the namespace of the service. Required
  , apiextensionsV1ServiceReferencePath :: !(Maybe Text) -- ^ "path" - path is an optional URL path at which the webhook will be contacted.
  , apiextensionsV1ServiceReferencePort :: !(Maybe Int) -- ^ "port" - port is an optional service port at which the webhook will be contacted. &#x60;port&#x60; should be a valid port number (1-65535, inclusive). Defaults to 443 for backward compatibility.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ApiextensionsV1ServiceReference
instance A.FromJSON ApiextensionsV1ServiceReference where
  parseJSON = A.withObject "ApiextensionsV1ServiceReference" $ \o ->
    ApiextensionsV1ServiceReference
      <$> (o .:  "name")
      <*> (o .:  "namespace")
      <*> (o .:? "path")
      <*> (o .:? "port")

-- | ToJSON ApiextensionsV1ServiceReference
instance A.ToJSON ApiextensionsV1ServiceReference where
  toJSON ApiextensionsV1ServiceReference {..} =
   _omitNulls
      [ "name" .= apiextensionsV1ServiceReferenceName
      , "namespace" .= apiextensionsV1ServiceReferenceNamespace
      , "path" .= apiextensionsV1ServiceReferencePath
      , "port" .= apiextensionsV1ServiceReferencePort
      ]


-- | Construct a value of type 'ApiextensionsV1ServiceReference' (by applying it's required fields, if any)
mkApiextensionsV1ServiceReference
  :: Text -- ^ 'apiextensionsV1ServiceReferenceName': name is the name of the service. Required
  -> Text -- ^ 'apiextensionsV1ServiceReferenceNamespace': namespace is the namespace of the service. Required
  -> ApiextensionsV1ServiceReference
mkApiextensionsV1ServiceReference apiextensionsV1ServiceReferenceName apiextensionsV1ServiceReferenceNamespace =
  ApiextensionsV1ServiceReference
  { apiextensionsV1ServiceReferenceName
  , apiextensionsV1ServiceReferenceNamespace
  , apiextensionsV1ServiceReferencePath = Nothing
  , apiextensionsV1ServiceReferencePort = Nothing
  }

-- ** ApiextensionsV1WebhookClientConfig
-- | ApiextensionsV1WebhookClientConfig
-- WebhookClientConfig contains the information to make a TLS connection with the webhook.
data ApiextensionsV1WebhookClientConfig = ApiextensionsV1WebhookClientConfig
  { apiextensionsV1WebhookClientConfigCaBundle :: !(Maybe ByteArray) -- ^ "caBundle" - caBundle is a PEM encoded CA bundle which will be used to validate the webhook&#39;s server certificate. If unspecified, system trust roots on the apiserver are used.
  , apiextensionsV1WebhookClientConfigService :: !(Maybe ApiextensionsV1ServiceReference) -- ^ "service"
  , apiextensionsV1WebhookClientConfigUrl :: !(Maybe Text) -- ^ "url" - url gives the location of the webhook, in standard URL form (&#x60;scheme://host:port/path&#x60;). Exactly one of &#x60;url&#x60; or &#x60;service&#x60; must be specified.  The &#x60;host&#x60; should not refer to a service running in the cluster; use the &#x60;service&#x60; field instead. The host might be resolved via external DNS in some apiservers (e.g., &#x60;kube-apiserver&#x60; cannot resolve in-cluster DNS as that would be a layering violation). &#x60;host&#x60; may also be an IP address.  Please note that using &#x60;localhost&#x60; or &#x60;127.0.0.1&#x60; as a &#x60;host&#x60; is risky unless you take great care to run this webhook on all hosts which run an apiserver which might need to make calls to this webhook. Such installs are likely to be non-portable, i.e., not easy to turn up in a new cluster.  The scheme must be \&quot;https\&quot;; the URL must begin with \&quot;https://\&quot;.  A path is optional, and if present may be any string permissible in a URL. You may use the path to pass an arbitrary string to the webhook, for example, a cluster identifier.  Attempting to use a user or basic auth e.g. \&quot;user:password@\&quot; is not allowed. Fragments (\&quot;#...\&quot;) and query parameters (\&quot;?...\&quot;) are not allowed, either.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ApiextensionsV1WebhookClientConfig
instance A.FromJSON ApiextensionsV1WebhookClientConfig where
  parseJSON = A.withObject "ApiextensionsV1WebhookClientConfig" $ \o ->
    ApiextensionsV1WebhookClientConfig
      <$> (o .:? "caBundle")
      <*> (o .:? "service")
      <*> (o .:? "url")

-- | ToJSON ApiextensionsV1WebhookClientConfig
instance A.ToJSON ApiextensionsV1WebhookClientConfig where
  toJSON ApiextensionsV1WebhookClientConfig {..} =
   _omitNulls
      [ "caBundle" .= apiextensionsV1WebhookClientConfigCaBundle
      , "service" .= apiextensionsV1WebhookClientConfigService
      , "url" .= apiextensionsV1WebhookClientConfigUrl
      ]


-- | Construct a value of type 'ApiextensionsV1WebhookClientConfig' (by applying it's required fields, if any)
mkApiextensionsV1WebhookClientConfig
  :: ApiextensionsV1WebhookClientConfig
mkApiextensionsV1WebhookClientConfig =
  ApiextensionsV1WebhookClientConfig
  { apiextensionsV1WebhookClientConfigCaBundle = Nothing
  , apiextensionsV1WebhookClientConfigService = Nothing
  , apiextensionsV1WebhookClientConfigUrl = Nothing
  }

-- ** ApiextensionsV1beta1ServiceReference
-- | ApiextensionsV1beta1ServiceReference
-- ServiceReference holds a reference to Service.legacy.k8s.io
data ApiextensionsV1beta1ServiceReference = ApiextensionsV1beta1ServiceReference
  { apiextensionsV1beta1ServiceReferenceName :: !(Text) -- ^ /Required/ "name" - name is the name of the service. Required
  , apiextensionsV1beta1ServiceReferenceNamespace :: !(Text) -- ^ /Required/ "namespace" - namespace is the namespace of the service. Required
  , apiextensionsV1beta1ServiceReferencePath :: !(Maybe Text) -- ^ "path" - path is an optional URL path at which the webhook will be contacted.
  , apiextensionsV1beta1ServiceReferencePort :: !(Maybe Int) -- ^ "port" - port is an optional service port at which the webhook will be contacted. &#x60;port&#x60; should be a valid port number (1-65535, inclusive). Defaults to 443 for backward compatibility.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ApiextensionsV1beta1ServiceReference
instance A.FromJSON ApiextensionsV1beta1ServiceReference where
  parseJSON = A.withObject "ApiextensionsV1beta1ServiceReference" $ \o ->
    ApiextensionsV1beta1ServiceReference
      <$> (o .:  "name")
      <*> (o .:  "namespace")
      <*> (o .:? "path")
      <*> (o .:? "port")

-- | ToJSON ApiextensionsV1beta1ServiceReference
instance A.ToJSON ApiextensionsV1beta1ServiceReference where
  toJSON ApiextensionsV1beta1ServiceReference {..} =
   _omitNulls
      [ "name" .= apiextensionsV1beta1ServiceReferenceName
      , "namespace" .= apiextensionsV1beta1ServiceReferenceNamespace
      , "path" .= apiextensionsV1beta1ServiceReferencePath
      , "port" .= apiextensionsV1beta1ServiceReferencePort
      ]


-- | Construct a value of type 'ApiextensionsV1beta1ServiceReference' (by applying it's required fields, if any)
mkApiextensionsV1beta1ServiceReference
  :: Text -- ^ 'apiextensionsV1beta1ServiceReferenceName': name is the name of the service. Required
  -> Text -- ^ 'apiextensionsV1beta1ServiceReferenceNamespace': namespace is the namespace of the service. Required
  -> ApiextensionsV1beta1ServiceReference
mkApiextensionsV1beta1ServiceReference apiextensionsV1beta1ServiceReferenceName apiextensionsV1beta1ServiceReferenceNamespace =
  ApiextensionsV1beta1ServiceReference
  { apiextensionsV1beta1ServiceReferenceName
  , apiextensionsV1beta1ServiceReferenceNamespace
  , apiextensionsV1beta1ServiceReferencePath = Nothing
  , apiextensionsV1beta1ServiceReferencePort = Nothing
  }

-- ** ApiextensionsV1beta1WebhookClientConfig
-- | ApiextensionsV1beta1WebhookClientConfig
-- WebhookClientConfig contains the information to make a TLS connection with the webhook.
data ApiextensionsV1beta1WebhookClientConfig = ApiextensionsV1beta1WebhookClientConfig
  { apiextensionsV1beta1WebhookClientConfigCaBundle :: !(Maybe ByteArray) -- ^ "caBundle" - caBundle is a PEM encoded CA bundle which will be used to validate the webhook&#39;s server certificate. If unspecified, system trust roots on the apiserver are used.
  , apiextensionsV1beta1WebhookClientConfigService :: !(Maybe ApiextensionsV1beta1ServiceReference) -- ^ "service"
  , apiextensionsV1beta1WebhookClientConfigUrl :: !(Maybe Text) -- ^ "url" - url gives the location of the webhook, in standard URL form (&#x60;scheme://host:port/path&#x60;). Exactly one of &#x60;url&#x60; or &#x60;service&#x60; must be specified.  The &#x60;host&#x60; should not refer to a service running in the cluster; use the &#x60;service&#x60; field instead. The host might be resolved via external DNS in some apiservers (e.g., &#x60;kube-apiserver&#x60; cannot resolve in-cluster DNS as that would be a layering violation). &#x60;host&#x60; may also be an IP address.  Please note that using &#x60;localhost&#x60; or &#x60;127.0.0.1&#x60; as a &#x60;host&#x60; is risky unless you take great care to run this webhook on all hosts which run an apiserver which might need to make calls to this webhook. Such installs are likely to be non-portable, i.e., not easy to turn up in a new cluster.  The scheme must be \&quot;https\&quot;; the URL must begin with \&quot;https://\&quot;.  A path is optional, and if present may be any string permissible in a URL. You may use the path to pass an arbitrary string to the webhook, for example, a cluster identifier.  Attempting to use a user or basic auth e.g. \&quot;user:password@\&quot; is not allowed. Fragments (\&quot;#...\&quot;) and query parameters (\&quot;?...\&quot;) are not allowed, either.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ApiextensionsV1beta1WebhookClientConfig
instance A.FromJSON ApiextensionsV1beta1WebhookClientConfig where
  parseJSON = A.withObject "ApiextensionsV1beta1WebhookClientConfig" $ \o ->
    ApiextensionsV1beta1WebhookClientConfig
      <$> (o .:? "caBundle")
      <*> (o .:? "service")
      <*> (o .:? "url")

-- | ToJSON ApiextensionsV1beta1WebhookClientConfig
instance A.ToJSON ApiextensionsV1beta1WebhookClientConfig where
  toJSON ApiextensionsV1beta1WebhookClientConfig {..} =
   _omitNulls
      [ "caBundle" .= apiextensionsV1beta1WebhookClientConfigCaBundle
      , "service" .= apiextensionsV1beta1WebhookClientConfigService
      , "url" .= apiextensionsV1beta1WebhookClientConfigUrl
      ]


-- | Construct a value of type 'ApiextensionsV1beta1WebhookClientConfig' (by applying it's required fields, if any)
mkApiextensionsV1beta1WebhookClientConfig
  :: ApiextensionsV1beta1WebhookClientConfig
mkApiextensionsV1beta1WebhookClientConfig =
  ApiextensionsV1beta1WebhookClientConfig
  { apiextensionsV1beta1WebhookClientConfigCaBundle = Nothing
  , apiextensionsV1beta1WebhookClientConfigService = Nothing
  , apiextensionsV1beta1WebhookClientConfigUrl = Nothing
  }

-- ** ApiregistrationV1ServiceReference
-- | ApiregistrationV1ServiceReference
-- ServiceReference holds a reference to Service.legacy.k8s.io
data ApiregistrationV1ServiceReference = ApiregistrationV1ServiceReference
  { apiregistrationV1ServiceReferenceName :: !(Maybe Text) -- ^ "name" - Name is the name of the service
  , apiregistrationV1ServiceReferenceNamespace :: !(Maybe Text) -- ^ "namespace" - Namespace is the namespace of the service
  , apiregistrationV1ServiceReferencePort :: !(Maybe Int) -- ^ "port" - If specified, the port on the service that hosting webhook. Default to 443 for backward compatibility. &#x60;port&#x60; should be a valid port number (1-65535, inclusive).
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ApiregistrationV1ServiceReference
instance A.FromJSON ApiregistrationV1ServiceReference where
  parseJSON = A.withObject "ApiregistrationV1ServiceReference" $ \o ->
    ApiregistrationV1ServiceReference
      <$> (o .:? "name")
      <*> (o .:? "namespace")
      <*> (o .:? "port")

-- | ToJSON ApiregistrationV1ServiceReference
instance A.ToJSON ApiregistrationV1ServiceReference where
  toJSON ApiregistrationV1ServiceReference {..} =
   _omitNulls
      [ "name" .= apiregistrationV1ServiceReferenceName
      , "namespace" .= apiregistrationV1ServiceReferenceNamespace
      , "port" .= apiregistrationV1ServiceReferencePort
      ]


-- | Construct a value of type 'ApiregistrationV1ServiceReference' (by applying it's required fields, if any)
mkApiregistrationV1ServiceReference
  :: ApiregistrationV1ServiceReference
mkApiregistrationV1ServiceReference =
  ApiregistrationV1ServiceReference
  { apiregistrationV1ServiceReferenceName = Nothing
  , apiregistrationV1ServiceReferenceNamespace = Nothing
  , apiregistrationV1ServiceReferencePort = Nothing
  }

-- ** ApiregistrationV1beta1ServiceReference
-- | ApiregistrationV1beta1ServiceReference
-- ServiceReference holds a reference to Service.legacy.k8s.io
data ApiregistrationV1beta1ServiceReference = ApiregistrationV1beta1ServiceReference
  { apiregistrationV1beta1ServiceReferenceName :: !(Maybe Text) -- ^ "name" - Name is the name of the service
  , apiregistrationV1beta1ServiceReferenceNamespace :: !(Maybe Text) -- ^ "namespace" - Namespace is the namespace of the service
  , apiregistrationV1beta1ServiceReferencePort :: !(Maybe Int) -- ^ "port" - If specified, the port on the service that hosting webhook. Default to 443 for backward compatibility. &#x60;port&#x60; should be a valid port number (1-65535, inclusive).
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ApiregistrationV1beta1ServiceReference
instance A.FromJSON ApiregistrationV1beta1ServiceReference where
  parseJSON = A.withObject "ApiregistrationV1beta1ServiceReference" $ \o ->
    ApiregistrationV1beta1ServiceReference
      <$> (o .:? "name")
      <*> (o .:? "namespace")
      <*> (o .:? "port")

-- | ToJSON ApiregistrationV1beta1ServiceReference
instance A.ToJSON ApiregistrationV1beta1ServiceReference where
  toJSON ApiregistrationV1beta1ServiceReference {..} =
   _omitNulls
      [ "name" .= apiregistrationV1beta1ServiceReferenceName
      , "namespace" .= apiregistrationV1beta1ServiceReferenceNamespace
      , "port" .= apiregistrationV1beta1ServiceReferencePort
      ]


-- | Construct a value of type 'ApiregistrationV1beta1ServiceReference' (by applying it's required fields, if any)
mkApiregistrationV1beta1ServiceReference
  :: ApiregistrationV1beta1ServiceReference
mkApiregistrationV1beta1ServiceReference =
  ApiregistrationV1beta1ServiceReference
  { apiregistrationV1beta1ServiceReferenceName = Nothing
  , apiregistrationV1beta1ServiceReferenceNamespace = Nothing
  , apiregistrationV1beta1ServiceReferencePort = Nothing
  }

-- ** AppsV1beta1Deployment
-- | AppsV1beta1Deployment
-- DEPRECATED - This group version of Deployment is deprecated by apps/v1beta2/Deployment. See the release notes for more information. Deployment enables declarative updates for Pods and ReplicaSets.
data AppsV1beta1Deployment = AppsV1beta1Deployment
  { appsV1beta1DeploymentApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , appsV1beta1DeploymentKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , appsV1beta1DeploymentMetadata :: !(Maybe V1ObjectMeta) -- ^ "metadata"
  , appsV1beta1DeploymentSpec :: !(Maybe AppsV1beta1DeploymentSpec) -- ^ "spec"
  , appsV1beta1DeploymentStatus :: !(Maybe AppsV1beta1DeploymentStatus) -- ^ "status"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AppsV1beta1Deployment
instance A.FromJSON AppsV1beta1Deployment where
  parseJSON = A.withObject "AppsV1beta1Deployment" $ \o ->
    AppsV1beta1Deployment
      <$> (o .:? "apiVersion")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")
      <*> (o .:? "spec")
      <*> (o .:? "status")

-- | ToJSON AppsV1beta1Deployment
instance A.ToJSON AppsV1beta1Deployment where
  toJSON AppsV1beta1Deployment {..} =
   _omitNulls
      [ "apiVersion" .= appsV1beta1DeploymentApiVersion
      , "kind" .= appsV1beta1DeploymentKind
      , "metadata" .= appsV1beta1DeploymentMetadata
      , "spec" .= appsV1beta1DeploymentSpec
      , "status" .= appsV1beta1DeploymentStatus
      ]


-- | Construct a value of type 'AppsV1beta1Deployment' (by applying it's required fields, if any)
mkAppsV1beta1Deployment
  :: AppsV1beta1Deployment
mkAppsV1beta1Deployment =
  AppsV1beta1Deployment
  { appsV1beta1DeploymentApiVersion = Nothing
  , appsV1beta1DeploymentKind = Nothing
  , appsV1beta1DeploymentMetadata = Nothing
  , appsV1beta1DeploymentSpec = Nothing
  , appsV1beta1DeploymentStatus = Nothing
  }

-- ** AppsV1beta1DeploymentCondition
-- | AppsV1beta1DeploymentCondition
-- DeploymentCondition describes the state of a deployment at a certain point.
data AppsV1beta1DeploymentCondition = AppsV1beta1DeploymentCondition
  { appsV1beta1DeploymentConditionLastTransitionTime :: !(Maybe DateTime) -- ^ "lastTransitionTime" - Last time the condition transitioned from one status to another.
  , appsV1beta1DeploymentConditionLastUpdateTime :: !(Maybe DateTime) -- ^ "lastUpdateTime" - The last time this condition was updated.
  , appsV1beta1DeploymentConditionMessage :: !(Maybe Text) -- ^ "message" - A human readable message indicating details about the transition.
  , appsV1beta1DeploymentConditionReason :: !(Maybe Text) -- ^ "reason" - The reason for the condition&#39;s last transition.
  , appsV1beta1DeploymentConditionStatus :: !(Text) -- ^ /Required/ "status" - Status of the condition, one of True, False, Unknown.
  , appsV1beta1DeploymentConditionType :: !(Text) -- ^ /Required/ "type" - Type of deployment condition.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AppsV1beta1DeploymentCondition
instance A.FromJSON AppsV1beta1DeploymentCondition where
  parseJSON = A.withObject "AppsV1beta1DeploymentCondition" $ \o ->
    AppsV1beta1DeploymentCondition
      <$> (o .:? "lastTransitionTime")
      <*> (o .:? "lastUpdateTime")
      <*> (o .:? "message")
      <*> (o .:? "reason")
      <*> (o .:  "status")
      <*> (o .:  "type")

-- | ToJSON AppsV1beta1DeploymentCondition
instance A.ToJSON AppsV1beta1DeploymentCondition where
  toJSON AppsV1beta1DeploymentCondition {..} =
   _omitNulls
      [ "lastTransitionTime" .= appsV1beta1DeploymentConditionLastTransitionTime
      , "lastUpdateTime" .= appsV1beta1DeploymentConditionLastUpdateTime
      , "message" .= appsV1beta1DeploymentConditionMessage
      , "reason" .= appsV1beta1DeploymentConditionReason
      , "status" .= appsV1beta1DeploymentConditionStatus
      , "type" .= appsV1beta1DeploymentConditionType
      ]


-- | Construct a value of type 'AppsV1beta1DeploymentCondition' (by applying it's required fields, if any)
mkAppsV1beta1DeploymentCondition
  :: Text -- ^ 'appsV1beta1DeploymentConditionStatus': Status of the condition, one of True, False, Unknown.
  -> Text -- ^ 'appsV1beta1DeploymentConditionType': Type of deployment condition.
  -> AppsV1beta1DeploymentCondition
mkAppsV1beta1DeploymentCondition appsV1beta1DeploymentConditionStatus appsV1beta1DeploymentConditionType =
  AppsV1beta1DeploymentCondition
  { appsV1beta1DeploymentConditionLastTransitionTime = Nothing
  , appsV1beta1DeploymentConditionLastUpdateTime = Nothing
  , appsV1beta1DeploymentConditionMessage = Nothing
  , appsV1beta1DeploymentConditionReason = Nothing
  , appsV1beta1DeploymentConditionStatus
  , appsV1beta1DeploymentConditionType
  }

-- ** AppsV1beta1DeploymentList
-- | AppsV1beta1DeploymentList
-- DeploymentList is a list of Deployments.
data AppsV1beta1DeploymentList = AppsV1beta1DeploymentList
  { appsV1beta1DeploymentListApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , appsV1beta1DeploymentListItems :: !([AppsV1beta1Deployment]) -- ^ /Required/ "items" - Items is the list of Deployments.
  , appsV1beta1DeploymentListKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , appsV1beta1DeploymentListMetadata :: !(Maybe V1ListMeta) -- ^ "metadata"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AppsV1beta1DeploymentList
instance A.FromJSON AppsV1beta1DeploymentList where
  parseJSON = A.withObject "AppsV1beta1DeploymentList" $ \o ->
    AppsV1beta1DeploymentList
      <$> (o .:? "apiVersion")
      <*> (o .:  "items")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")

-- | ToJSON AppsV1beta1DeploymentList
instance A.ToJSON AppsV1beta1DeploymentList where
  toJSON AppsV1beta1DeploymentList {..} =
   _omitNulls
      [ "apiVersion" .= appsV1beta1DeploymentListApiVersion
      , "items" .= appsV1beta1DeploymentListItems
      , "kind" .= appsV1beta1DeploymentListKind
      , "metadata" .= appsV1beta1DeploymentListMetadata
      ]


-- | Construct a value of type 'AppsV1beta1DeploymentList' (by applying it's required fields, if any)
mkAppsV1beta1DeploymentList
  :: [AppsV1beta1Deployment] -- ^ 'appsV1beta1DeploymentListItems': Items is the list of Deployments.
  -> AppsV1beta1DeploymentList
mkAppsV1beta1DeploymentList appsV1beta1DeploymentListItems =
  AppsV1beta1DeploymentList
  { appsV1beta1DeploymentListApiVersion = Nothing
  , appsV1beta1DeploymentListItems
  , appsV1beta1DeploymentListKind = Nothing
  , appsV1beta1DeploymentListMetadata = Nothing
  }

-- ** AppsV1beta1DeploymentRollback
-- | AppsV1beta1DeploymentRollback
-- DEPRECATED. DeploymentRollback stores the information required to rollback a deployment.
data AppsV1beta1DeploymentRollback = AppsV1beta1DeploymentRollback
  { appsV1beta1DeploymentRollbackApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , appsV1beta1DeploymentRollbackKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , appsV1beta1DeploymentRollbackName :: !(Text) -- ^ /Required/ "name" - Required: This must match the Name of a deployment.
  , appsV1beta1DeploymentRollbackRollbackTo :: !(AppsV1beta1RollbackConfig) -- ^ /Required/ "rollbackTo"
  , appsV1beta1DeploymentRollbackUpdatedAnnotations :: !(Maybe (Map.Map String Text)) -- ^ "updatedAnnotations" - The annotations to be updated to a deployment
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AppsV1beta1DeploymentRollback
instance A.FromJSON AppsV1beta1DeploymentRollback where
  parseJSON = A.withObject "AppsV1beta1DeploymentRollback" $ \o ->
    AppsV1beta1DeploymentRollback
      <$> (o .:? "apiVersion")
      <*> (o .:? "kind")
      <*> (o .:  "name")
      <*> (o .:  "rollbackTo")
      <*> (o .:? "updatedAnnotations")

-- | ToJSON AppsV1beta1DeploymentRollback
instance A.ToJSON AppsV1beta1DeploymentRollback where
  toJSON AppsV1beta1DeploymentRollback {..} =
   _omitNulls
      [ "apiVersion" .= appsV1beta1DeploymentRollbackApiVersion
      , "kind" .= appsV1beta1DeploymentRollbackKind
      , "name" .= appsV1beta1DeploymentRollbackName
      , "rollbackTo" .= appsV1beta1DeploymentRollbackRollbackTo
      , "updatedAnnotations" .= appsV1beta1DeploymentRollbackUpdatedAnnotations
      ]


-- | Construct a value of type 'AppsV1beta1DeploymentRollback' (by applying it's required fields, if any)
mkAppsV1beta1DeploymentRollback
  :: Text -- ^ 'appsV1beta1DeploymentRollbackName': Required: This must match the Name of a deployment.
  -> AppsV1beta1RollbackConfig -- ^ 'appsV1beta1DeploymentRollbackRollbackTo' 
  -> AppsV1beta1DeploymentRollback
mkAppsV1beta1DeploymentRollback appsV1beta1DeploymentRollbackName appsV1beta1DeploymentRollbackRollbackTo =
  AppsV1beta1DeploymentRollback
  { appsV1beta1DeploymentRollbackApiVersion = Nothing
  , appsV1beta1DeploymentRollbackKind = Nothing
  , appsV1beta1DeploymentRollbackName
  , appsV1beta1DeploymentRollbackRollbackTo
  , appsV1beta1DeploymentRollbackUpdatedAnnotations = Nothing
  }

-- ** AppsV1beta1DeploymentSpec
-- | AppsV1beta1DeploymentSpec
-- DeploymentSpec is the specification of the desired behavior of the Deployment.
data AppsV1beta1DeploymentSpec = AppsV1beta1DeploymentSpec
  { appsV1beta1DeploymentSpecMinReadySeconds :: !(Maybe Int) -- ^ "minReadySeconds" - Minimum number of seconds for which a newly created pod should be ready without any of its container crashing, for it to be considered available. Defaults to 0 (pod will be considered available as soon as it is ready)
  , appsV1beta1DeploymentSpecPaused :: !(Maybe Bool) -- ^ "paused" - Indicates that the deployment is paused.
  , appsV1beta1DeploymentSpecProgressDeadlineSeconds :: !(Maybe Int) -- ^ "progressDeadlineSeconds" - The maximum time in seconds for a deployment to make progress before it is considered to be failed. The deployment controller will continue to process failed deployments and a condition with a ProgressDeadlineExceeded reason will be surfaced in the deployment status. Note that progress will not be estimated during the time a deployment is paused. Defaults to 600s.
  , appsV1beta1DeploymentSpecReplicas :: !(Maybe Int) -- ^ "replicas" - Number of desired pods. This is a pointer to distinguish between explicit zero and not specified. Defaults to 1.
  , appsV1beta1DeploymentSpecRevisionHistoryLimit :: !(Maybe Int) -- ^ "revisionHistoryLimit" - The number of old ReplicaSets to retain to allow rollback. This is a pointer to distinguish between explicit zero and not specified. Defaults to 2.
  , appsV1beta1DeploymentSpecRollbackTo :: !(Maybe AppsV1beta1RollbackConfig) -- ^ "rollbackTo"
  , appsV1beta1DeploymentSpecSelector :: !(Maybe V1LabelSelector) -- ^ "selector"
  , appsV1beta1DeploymentSpecStrategy :: !(Maybe AppsV1beta1DeploymentStrategy) -- ^ "strategy"
  , appsV1beta1DeploymentSpecTemplate :: !(V1PodTemplateSpec) -- ^ /Required/ "template"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AppsV1beta1DeploymentSpec
instance A.FromJSON AppsV1beta1DeploymentSpec where
  parseJSON = A.withObject "AppsV1beta1DeploymentSpec" $ \o ->
    AppsV1beta1DeploymentSpec
      <$> (o .:? "minReadySeconds")
      <*> (o .:? "paused")
      <*> (o .:? "progressDeadlineSeconds")
      <*> (o .:? "replicas")
      <*> (o .:? "revisionHistoryLimit")
      <*> (o .:? "rollbackTo")
      <*> (o .:? "selector")
      <*> (o .:? "strategy")
      <*> (o .:  "template")

-- | ToJSON AppsV1beta1DeploymentSpec
instance A.ToJSON AppsV1beta1DeploymentSpec where
  toJSON AppsV1beta1DeploymentSpec {..} =
   _omitNulls
      [ "minReadySeconds" .= appsV1beta1DeploymentSpecMinReadySeconds
      , "paused" .= appsV1beta1DeploymentSpecPaused
      , "progressDeadlineSeconds" .= appsV1beta1DeploymentSpecProgressDeadlineSeconds
      , "replicas" .= appsV1beta1DeploymentSpecReplicas
      , "revisionHistoryLimit" .= appsV1beta1DeploymentSpecRevisionHistoryLimit
      , "rollbackTo" .= appsV1beta1DeploymentSpecRollbackTo
      , "selector" .= appsV1beta1DeploymentSpecSelector
      , "strategy" .= appsV1beta1DeploymentSpecStrategy
      , "template" .= appsV1beta1DeploymentSpecTemplate
      ]


-- | Construct a value of type 'AppsV1beta1DeploymentSpec' (by applying it's required fields, if any)
mkAppsV1beta1DeploymentSpec
  :: V1PodTemplateSpec -- ^ 'appsV1beta1DeploymentSpecTemplate' 
  -> AppsV1beta1DeploymentSpec
mkAppsV1beta1DeploymentSpec appsV1beta1DeploymentSpecTemplate =
  AppsV1beta1DeploymentSpec
  { appsV1beta1DeploymentSpecMinReadySeconds = Nothing
  , appsV1beta1DeploymentSpecPaused = Nothing
  , appsV1beta1DeploymentSpecProgressDeadlineSeconds = Nothing
  , appsV1beta1DeploymentSpecReplicas = Nothing
  , appsV1beta1DeploymentSpecRevisionHistoryLimit = Nothing
  , appsV1beta1DeploymentSpecRollbackTo = Nothing
  , appsV1beta1DeploymentSpecSelector = Nothing
  , appsV1beta1DeploymentSpecStrategy = Nothing
  , appsV1beta1DeploymentSpecTemplate
  }

-- ** AppsV1beta1DeploymentStatus
-- | AppsV1beta1DeploymentStatus
-- DeploymentStatus is the most recently observed status of the Deployment.
data AppsV1beta1DeploymentStatus = AppsV1beta1DeploymentStatus
  { appsV1beta1DeploymentStatusAvailableReplicas :: !(Maybe Int) -- ^ "availableReplicas" - Total number of available pods (ready for at least minReadySeconds) targeted by this deployment.
  , appsV1beta1DeploymentStatusCollisionCount :: !(Maybe Int) -- ^ "collisionCount" - Count of hash collisions for the Deployment. The Deployment controller uses this field as a collision avoidance mechanism when it needs to create the name for the newest ReplicaSet.
  , appsV1beta1DeploymentStatusConditions :: !(Maybe [AppsV1beta1DeploymentCondition]) -- ^ "conditions" - Represents the latest available observations of a deployment&#39;s current state.
  , appsV1beta1DeploymentStatusObservedGeneration :: !(Maybe Integer) -- ^ "observedGeneration" - The generation observed by the deployment controller.
  , appsV1beta1DeploymentStatusReadyReplicas :: !(Maybe Int) -- ^ "readyReplicas" - Total number of ready pods targeted by this deployment.
  , appsV1beta1DeploymentStatusReplicas :: !(Maybe Int) -- ^ "replicas" - Total number of non-terminated pods targeted by this deployment (their labels match the selector).
  , appsV1beta1DeploymentStatusUnavailableReplicas :: !(Maybe Int) -- ^ "unavailableReplicas" - Total number of unavailable pods targeted by this deployment. This is the total number of pods that are still required for the deployment to have 100% available capacity. They may either be pods that are running but not yet available or pods that still have not been created.
  , appsV1beta1DeploymentStatusUpdatedReplicas :: !(Maybe Int) -- ^ "updatedReplicas" - Total number of non-terminated pods targeted by this deployment that have the desired template spec.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AppsV1beta1DeploymentStatus
instance A.FromJSON AppsV1beta1DeploymentStatus where
  parseJSON = A.withObject "AppsV1beta1DeploymentStatus" $ \o ->
    AppsV1beta1DeploymentStatus
      <$> (o .:? "availableReplicas")
      <*> (o .:? "collisionCount")
      <*> (o .:? "conditions")
      <*> (o .:? "observedGeneration")
      <*> (o .:? "readyReplicas")
      <*> (o .:? "replicas")
      <*> (o .:? "unavailableReplicas")
      <*> (o .:? "updatedReplicas")

-- | ToJSON AppsV1beta1DeploymentStatus
instance A.ToJSON AppsV1beta1DeploymentStatus where
  toJSON AppsV1beta1DeploymentStatus {..} =
   _omitNulls
      [ "availableReplicas" .= appsV1beta1DeploymentStatusAvailableReplicas
      , "collisionCount" .= appsV1beta1DeploymentStatusCollisionCount
      , "conditions" .= appsV1beta1DeploymentStatusConditions
      , "observedGeneration" .= appsV1beta1DeploymentStatusObservedGeneration
      , "readyReplicas" .= appsV1beta1DeploymentStatusReadyReplicas
      , "replicas" .= appsV1beta1DeploymentStatusReplicas
      , "unavailableReplicas" .= appsV1beta1DeploymentStatusUnavailableReplicas
      , "updatedReplicas" .= appsV1beta1DeploymentStatusUpdatedReplicas
      ]


-- | Construct a value of type 'AppsV1beta1DeploymentStatus' (by applying it's required fields, if any)
mkAppsV1beta1DeploymentStatus
  :: AppsV1beta1DeploymentStatus
mkAppsV1beta1DeploymentStatus =
  AppsV1beta1DeploymentStatus
  { appsV1beta1DeploymentStatusAvailableReplicas = Nothing
  , appsV1beta1DeploymentStatusCollisionCount = Nothing
  , appsV1beta1DeploymentStatusConditions = Nothing
  , appsV1beta1DeploymentStatusObservedGeneration = Nothing
  , appsV1beta1DeploymentStatusReadyReplicas = Nothing
  , appsV1beta1DeploymentStatusReplicas = Nothing
  , appsV1beta1DeploymentStatusUnavailableReplicas = Nothing
  , appsV1beta1DeploymentStatusUpdatedReplicas = Nothing
  }

-- ** AppsV1beta1DeploymentStrategy
-- | AppsV1beta1DeploymentStrategy
-- DeploymentStrategy describes how to replace existing pods with new ones.
data AppsV1beta1DeploymentStrategy = AppsV1beta1DeploymentStrategy
  { appsV1beta1DeploymentStrategyRollingUpdate :: !(Maybe AppsV1beta1RollingUpdateDeployment) -- ^ "rollingUpdate"
  , appsV1beta1DeploymentStrategyType :: !(Maybe Text) -- ^ "type" - Type of deployment. Can be \&quot;Recreate\&quot; or \&quot;RollingUpdate\&quot;. Default is RollingUpdate.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AppsV1beta1DeploymentStrategy
instance A.FromJSON AppsV1beta1DeploymentStrategy where
  parseJSON = A.withObject "AppsV1beta1DeploymentStrategy" $ \o ->
    AppsV1beta1DeploymentStrategy
      <$> (o .:? "rollingUpdate")
      <*> (o .:? "type")

-- | ToJSON AppsV1beta1DeploymentStrategy
instance A.ToJSON AppsV1beta1DeploymentStrategy where
  toJSON AppsV1beta1DeploymentStrategy {..} =
   _omitNulls
      [ "rollingUpdate" .= appsV1beta1DeploymentStrategyRollingUpdate
      , "type" .= appsV1beta1DeploymentStrategyType
      ]


-- | Construct a value of type 'AppsV1beta1DeploymentStrategy' (by applying it's required fields, if any)
mkAppsV1beta1DeploymentStrategy
  :: AppsV1beta1DeploymentStrategy
mkAppsV1beta1DeploymentStrategy =
  AppsV1beta1DeploymentStrategy
  { appsV1beta1DeploymentStrategyRollingUpdate = Nothing
  , appsV1beta1DeploymentStrategyType = Nothing
  }

-- ** AppsV1beta1RollbackConfig
-- | AppsV1beta1RollbackConfig
-- DEPRECATED.
data AppsV1beta1RollbackConfig = AppsV1beta1RollbackConfig
  { appsV1beta1RollbackConfigRevision :: !(Maybe Integer) -- ^ "revision" - The revision to rollback to. If set to 0, rollback to the last revision.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AppsV1beta1RollbackConfig
instance A.FromJSON AppsV1beta1RollbackConfig where
  parseJSON = A.withObject "AppsV1beta1RollbackConfig" $ \o ->
    AppsV1beta1RollbackConfig
      <$> (o .:? "revision")

-- | ToJSON AppsV1beta1RollbackConfig
instance A.ToJSON AppsV1beta1RollbackConfig where
  toJSON AppsV1beta1RollbackConfig {..} =
   _omitNulls
      [ "revision" .= appsV1beta1RollbackConfigRevision
      ]


-- | Construct a value of type 'AppsV1beta1RollbackConfig' (by applying it's required fields, if any)
mkAppsV1beta1RollbackConfig
  :: AppsV1beta1RollbackConfig
mkAppsV1beta1RollbackConfig =
  AppsV1beta1RollbackConfig
  { appsV1beta1RollbackConfigRevision = Nothing
  }

-- ** AppsV1beta1RollingUpdateDeployment
-- | AppsV1beta1RollingUpdateDeployment
-- Spec to control the desired behavior of rolling update.
data AppsV1beta1RollingUpdateDeployment = AppsV1beta1RollingUpdateDeployment
  { appsV1beta1RollingUpdateDeploymentMaxSurge :: !(Maybe IntOrString) -- ^ "maxSurge"
  , appsV1beta1RollingUpdateDeploymentMaxUnavailable :: !(Maybe IntOrString) -- ^ "maxUnavailable"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AppsV1beta1RollingUpdateDeployment
instance A.FromJSON AppsV1beta1RollingUpdateDeployment where
  parseJSON = A.withObject "AppsV1beta1RollingUpdateDeployment" $ \o ->
    AppsV1beta1RollingUpdateDeployment
      <$> (o .:? "maxSurge")
      <*> (o .:? "maxUnavailable")

-- | ToJSON AppsV1beta1RollingUpdateDeployment
instance A.ToJSON AppsV1beta1RollingUpdateDeployment where
  toJSON AppsV1beta1RollingUpdateDeployment {..} =
   _omitNulls
      [ "maxSurge" .= appsV1beta1RollingUpdateDeploymentMaxSurge
      , "maxUnavailable" .= appsV1beta1RollingUpdateDeploymentMaxUnavailable
      ]


-- | Construct a value of type 'AppsV1beta1RollingUpdateDeployment' (by applying it's required fields, if any)
mkAppsV1beta1RollingUpdateDeployment
  :: AppsV1beta1RollingUpdateDeployment
mkAppsV1beta1RollingUpdateDeployment =
  AppsV1beta1RollingUpdateDeployment
  { appsV1beta1RollingUpdateDeploymentMaxSurge = Nothing
  , appsV1beta1RollingUpdateDeploymentMaxUnavailable = Nothing
  }

-- ** AppsV1beta1Scale
-- | AppsV1beta1Scale
-- Scale represents a scaling request for a resource.
data AppsV1beta1Scale = AppsV1beta1Scale
  { appsV1beta1ScaleApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , appsV1beta1ScaleKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , appsV1beta1ScaleMetadata :: !(Maybe V1ObjectMeta) -- ^ "metadata"
  , appsV1beta1ScaleSpec :: !(Maybe AppsV1beta1ScaleSpec) -- ^ "spec"
  , appsV1beta1ScaleStatus :: !(Maybe AppsV1beta1ScaleStatus) -- ^ "status"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AppsV1beta1Scale
instance A.FromJSON AppsV1beta1Scale where
  parseJSON = A.withObject "AppsV1beta1Scale" $ \o ->
    AppsV1beta1Scale
      <$> (o .:? "apiVersion")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")
      <*> (o .:? "spec")
      <*> (o .:? "status")

-- | ToJSON AppsV1beta1Scale
instance A.ToJSON AppsV1beta1Scale where
  toJSON AppsV1beta1Scale {..} =
   _omitNulls
      [ "apiVersion" .= appsV1beta1ScaleApiVersion
      , "kind" .= appsV1beta1ScaleKind
      , "metadata" .= appsV1beta1ScaleMetadata
      , "spec" .= appsV1beta1ScaleSpec
      , "status" .= appsV1beta1ScaleStatus
      ]


-- | Construct a value of type 'AppsV1beta1Scale' (by applying it's required fields, if any)
mkAppsV1beta1Scale
  :: AppsV1beta1Scale
mkAppsV1beta1Scale =
  AppsV1beta1Scale
  { appsV1beta1ScaleApiVersion = Nothing
  , appsV1beta1ScaleKind = Nothing
  , appsV1beta1ScaleMetadata = Nothing
  , appsV1beta1ScaleSpec = Nothing
  , appsV1beta1ScaleStatus = Nothing
  }

-- ** AppsV1beta1ScaleSpec
-- | AppsV1beta1ScaleSpec
-- ScaleSpec describes the attributes of a scale subresource
data AppsV1beta1ScaleSpec = AppsV1beta1ScaleSpec
  { appsV1beta1ScaleSpecReplicas :: !(Maybe Int) -- ^ "replicas" - desired number of instances for the scaled object.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AppsV1beta1ScaleSpec
instance A.FromJSON AppsV1beta1ScaleSpec where
  parseJSON = A.withObject "AppsV1beta1ScaleSpec" $ \o ->
    AppsV1beta1ScaleSpec
      <$> (o .:? "replicas")

-- | ToJSON AppsV1beta1ScaleSpec
instance A.ToJSON AppsV1beta1ScaleSpec where
  toJSON AppsV1beta1ScaleSpec {..} =
   _omitNulls
      [ "replicas" .= appsV1beta1ScaleSpecReplicas
      ]


-- | Construct a value of type 'AppsV1beta1ScaleSpec' (by applying it's required fields, if any)
mkAppsV1beta1ScaleSpec
  :: AppsV1beta1ScaleSpec
mkAppsV1beta1ScaleSpec =
  AppsV1beta1ScaleSpec
  { appsV1beta1ScaleSpecReplicas = Nothing
  }

-- ** AppsV1beta1ScaleStatus
-- | AppsV1beta1ScaleStatus
-- ScaleStatus represents the current status of a scale subresource.
data AppsV1beta1ScaleStatus = AppsV1beta1ScaleStatus
  { appsV1beta1ScaleStatusReplicas :: !(Int) -- ^ /Required/ "replicas" - actual number of observed instances of the scaled object.
  , appsV1beta1ScaleStatusSelector :: !(Maybe (Map.Map String Text)) -- ^ "selector" - label query over pods that should match the replicas count. More info: http://kubernetes.io/docs/user-guide/labels#label-selectors
  , appsV1beta1ScaleStatusTargetSelector :: !(Maybe Text) -- ^ "targetSelector" - label selector for pods that should match the replicas count. This is a serializated version of both map-based and more expressive set-based selectors. This is done to avoid introspection in the clients. The string will be in the same format as the query-param syntax. If the target type only supports map-based selectors, both this field and map-based selector field are populated. More info: https://kubernetes.io/docs/concepts/overview/working-with-objects/labels/#label-selectors
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON AppsV1beta1ScaleStatus
instance A.FromJSON AppsV1beta1ScaleStatus where
  parseJSON = A.withObject "AppsV1beta1ScaleStatus" $ \o ->
    AppsV1beta1ScaleStatus
      <$> (o .:  "replicas")
      <*> (o .:? "selector")
      <*> (o .:? "targetSelector")

-- | ToJSON AppsV1beta1ScaleStatus
instance A.ToJSON AppsV1beta1ScaleStatus where
  toJSON AppsV1beta1ScaleStatus {..} =
   _omitNulls
      [ "replicas" .= appsV1beta1ScaleStatusReplicas
      , "selector" .= appsV1beta1ScaleStatusSelector
      , "targetSelector" .= appsV1beta1ScaleStatusTargetSelector
      ]


-- | Construct a value of type 'AppsV1beta1ScaleStatus' (by applying it's required fields, if any)
mkAppsV1beta1ScaleStatus
  :: Int -- ^ 'appsV1beta1ScaleStatusReplicas': actual number of observed instances of the scaled object.
  -> AppsV1beta1ScaleStatus
mkAppsV1beta1ScaleStatus appsV1beta1ScaleStatusReplicas =
  AppsV1beta1ScaleStatus
  { appsV1beta1ScaleStatusReplicas
  , appsV1beta1ScaleStatusSelector = Nothing
  , appsV1beta1ScaleStatusTargetSelector = Nothing
  }

-- ** ExtensionsV1beta1AllowedCSIDriver
-- | ExtensionsV1beta1AllowedCSIDriver
-- AllowedCSIDriver represents a single inline CSI Driver that is allowed to be used.
data ExtensionsV1beta1AllowedCSIDriver = ExtensionsV1beta1AllowedCSIDriver
  { extensionsV1beta1AllowedCSIDriverName :: !(Text) -- ^ /Required/ "name" - Name is the registered name of the CSI driver
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1AllowedCSIDriver
instance A.FromJSON ExtensionsV1beta1AllowedCSIDriver where
  parseJSON = A.withObject "ExtensionsV1beta1AllowedCSIDriver" $ \o ->
    ExtensionsV1beta1AllowedCSIDriver
      <$> (o .:  "name")

-- | ToJSON ExtensionsV1beta1AllowedCSIDriver
instance A.ToJSON ExtensionsV1beta1AllowedCSIDriver where
  toJSON ExtensionsV1beta1AllowedCSIDriver {..} =
   _omitNulls
      [ "name" .= extensionsV1beta1AllowedCSIDriverName
      ]


-- | Construct a value of type 'ExtensionsV1beta1AllowedCSIDriver' (by applying it's required fields, if any)
mkExtensionsV1beta1AllowedCSIDriver
  :: Text -- ^ 'extensionsV1beta1AllowedCSIDriverName': Name is the registered name of the CSI driver
  -> ExtensionsV1beta1AllowedCSIDriver
mkExtensionsV1beta1AllowedCSIDriver extensionsV1beta1AllowedCSIDriverName =
  ExtensionsV1beta1AllowedCSIDriver
  { extensionsV1beta1AllowedCSIDriverName
  }

-- ** ExtensionsV1beta1AllowedFlexVolume
-- | ExtensionsV1beta1AllowedFlexVolume
-- AllowedFlexVolume represents a single Flexvolume that is allowed to be used. Deprecated: use AllowedFlexVolume from policy API Group instead.
data ExtensionsV1beta1AllowedFlexVolume = ExtensionsV1beta1AllowedFlexVolume
  { extensionsV1beta1AllowedFlexVolumeDriver :: !(Text) -- ^ /Required/ "driver" - driver is the name of the Flexvolume driver.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1AllowedFlexVolume
instance A.FromJSON ExtensionsV1beta1AllowedFlexVolume where
  parseJSON = A.withObject "ExtensionsV1beta1AllowedFlexVolume" $ \o ->
    ExtensionsV1beta1AllowedFlexVolume
      <$> (o .:  "driver")

-- | ToJSON ExtensionsV1beta1AllowedFlexVolume
instance A.ToJSON ExtensionsV1beta1AllowedFlexVolume where
  toJSON ExtensionsV1beta1AllowedFlexVolume {..} =
   _omitNulls
      [ "driver" .= extensionsV1beta1AllowedFlexVolumeDriver
      ]


-- | Construct a value of type 'ExtensionsV1beta1AllowedFlexVolume' (by applying it's required fields, if any)
mkExtensionsV1beta1AllowedFlexVolume
  :: Text -- ^ 'extensionsV1beta1AllowedFlexVolumeDriver': driver is the name of the Flexvolume driver.
  -> ExtensionsV1beta1AllowedFlexVolume
mkExtensionsV1beta1AllowedFlexVolume extensionsV1beta1AllowedFlexVolumeDriver =
  ExtensionsV1beta1AllowedFlexVolume
  { extensionsV1beta1AllowedFlexVolumeDriver
  }

-- ** ExtensionsV1beta1AllowedHostPath
-- | ExtensionsV1beta1AllowedHostPath
-- AllowedHostPath defines the host volume conditions that will be enabled by a policy for pods to use. It requires the path prefix to be defined. Deprecated: use AllowedHostPath from policy API Group instead.
data ExtensionsV1beta1AllowedHostPath = ExtensionsV1beta1AllowedHostPath
  { extensionsV1beta1AllowedHostPathPathPrefix :: !(Maybe Text) -- ^ "pathPrefix" - pathPrefix is the path prefix that the host volume must match. It does not support &#x60;*&#x60;. Trailing slashes are trimmed when validating the path prefix with a host path.  Examples: &#x60;/foo&#x60; would allow &#x60;/foo&#x60;, &#x60;/foo/&#x60; and &#x60;/foo/bar&#x60; &#x60;/foo&#x60; would not allow &#x60;/food&#x60; or &#x60;/etc/foo&#x60;
  , extensionsV1beta1AllowedHostPathReadOnly :: !(Maybe Bool) -- ^ "readOnly" - when set to true, will allow host volumes matching the pathPrefix only if all volume mounts are readOnly.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1AllowedHostPath
instance A.FromJSON ExtensionsV1beta1AllowedHostPath where
  parseJSON = A.withObject "ExtensionsV1beta1AllowedHostPath" $ \o ->
    ExtensionsV1beta1AllowedHostPath
      <$> (o .:? "pathPrefix")
      <*> (o .:? "readOnly")

-- | ToJSON ExtensionsV1beta1AllowedHostPath
instance A.ToJSON ExtensionsV1beta1AllowedHostPath where
  toJSON ExtensionsV1beta1AllowedHostPath {..} =
   _omitNulls
      [ "pathPrefix" .= extensionsV1beta1AllowedHostPathPathPrefix
      , "readOnly" .= extensionsV1beta1AllowedHostPathReadOnly
      ]


-- | Construct a value of type 'ExtensionsV1beta1AllowedHostPath' (by applying it's required fields, if any)
mkExtensionsV1beta1AllowedHostPath
  :: ExtensionsV1beta1AllowedHostPath
mkExtensionsV1beta1AllowedHostPath =
  ExtensionsV1beta1AllowedHostPath
  { extensionsV1beta1AllowedHostPathPathPrefix = Nothing
  , extensionsV1beta1AllowedHostPathReadOnly = Nothing
  }

-- ** ExtensionsV1beta1Deployment
-- | ExtensionsV1beta1Deployment
-- DEPRECATED - This group version of Deployment is deprecated by apps/v1beta2/Deployment. See the release notes for more information. Deployment enables declarative updates for Pods and ReplicaSets.
data ExtensionsV1beta1Deployment = ExtensionsV1beta1Deployment
  { extensionsV1beta1DeploymentApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , extensionsV1beta1DeploymentKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , extensionsV1beta1DeploymentMetadata :: !(Maybe V1ObjectMeta) -- ^ "metadata"
  , extensionsV1beta1DeploymentSpec :: !(Maybe ExtensionsV1beta1DeploymentSpec) -- ^ "spec"
  , extensionsV1beta1DeploymentStatus :: !(Maybe ExtensionsV1beta1DeploymentStatus) -- ^ "status"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1Deployment
instance A.FromJSON ExtensionsV1beta1Deployment where
  parseJSON = A.withObject "ExtensionsV1beta1Deployment" $ \o ->
    ExtensionsV1beta1Deployment
      <$> (o .:? "apiVersion")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")
      <*> (o .:? "spec")
      <*> (o .:? "status")

-- | ToJSON ExtensionsV1beta1Deployment
instance A.ToJSON ExtensionsV1beta1Deployment where
  toJSON ExtensionsV1beta1Deployment {..} =
   _omitNulls
      [ "apiVersion" .= extensionsV1beta1DeploymentApiVersion
      , "kind" .= extensionsV1beta1DeploymentKind
      , "metadata" .= extensionsV1beta1DeploymentMetadata
      , "spec" .= extensionsV1beta1DeploymentSpec
      , "status" .= extensionsV1beta1DeploymentStatus
      ]


-- | Construct a value of type 'ExtensionsV1beta1Deployment' (by applying it's required fields, if any)
mkExtensionsV1beta1Deployment
  :: ExtensionsV1beta1Deployment
mkExtensionsV1beta1Deployment =
  ExtensionsV1beta1Deployment
  { extensionsV1beta1DeploymentApiVersion = Nothing
  , extensionsV1beta1DeploymentKind = Nothing
  , extensionsV1beta1DeploymentMetadata = Nothing
  , extensionsV1beta1DeploymentSpec = Nothing
  , extensionsV1beta1DeploymentStatus = Nothing
  }

-- ** ExtensionsV1beta1DeploymentCondition
-- | ExtensionsV1beta1DeploymentCondition
-- DeploymentCondition describes the state of a deployment at a certain point.
data ExtensionsV1beta1DeploymentCondition = ExtensionsV1beta1DeploymentCondition
  { extensionsV1beta1DeploymentConditionLastTransitionTime :: !(Maybe DateTime) -- ^ "lastTransitionTime" - Last time the condition transitioned from one status to another.
  , extensionsV1beta1DeploymentConditionLastUpdateTime :: !(Maybe DateTime) -- ^ "lastUpdateTime" - The last time this condition was updated.
  , extensionsV1beta1DeploymentConditionMessage :: !(Maybe Text) -- ^ "message" - A human readable message indicating details about the transition.
  , extensionsV1beta1DeploymentConditionReason :: !(Maybe Text) -- ^ "reason" - The reason for the condition&#39;s last transition.
  , extensionsV1beta1DeploymentConditionStatus :: !(Text) -- ^ /Required/ "status" - Status of the condition, one of True, False, Unknown.
  , extensionsV1beta1DeploymentConditionType :: !(Text) -- ^ /Required/ "type" - Type of deployment condition.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1DeploymentCondition
instance A.FromJSON ExtensionsV1beta1DeploymentCondition where
  parseJSON = A.withObject "ExtensionsV1beta1DeploymentCondition" $ \o ->
    ExtensionsV1beta1DeploymentCondition
      <$> (o .:? "lastTransitionTime")
      <*> (o .:? "lastUpdateTime")
      <*> (o .:? "message")
      <*> (o .:? "reason")
      <*> (o .:  "status")
      <*> (o .:  "type")

-- | ToJSON ExtensionsV1beta1DeploymentCondition
instance A.ToJSON ExtensionsV1beta1DeploymentCondition where
  toJSON ExtensionsV1beta1DeploymentCondition {..} =
   _omitNulls
      [ "lastTransitionTime" .= extensionsV1beta1DeploymentConditionLastTransitionTime
      , "lastUpdateTime" .= extensionsV1beta1DeploymentConditionLastUpdateTime
      , "message" .= extensionsV1beta1DeploymentConditionMessage
      , "reason" .= extensionsV1beta1DeploymentConditionReason
      , "status" .= extensionsV1beta1DeploymentConditionStatus
      , "type" .= extensionsV1beta1DeploymentConditionType
      ]


-- | Construct a value of type 'ExtensionsV1beta1DeploymentCondition' (by applying it's required fields, if any)
mkExtensionsV1beta1DeploymentCondition
  :: Text -- ^ 'extensionsV1beta1DeploymentConditionStatus': Status of the condition, one of True, False, Unknown.
  -> Text -- ^ 'extensionsV1beta1DeploymentConditionType': Type of deployment condition.
  -> ExtensionsV1beta1DeploymentCondition
mkExtensionsV1beta1DeploymentCondition extensionsV1beta1DeploymentConditionStatus extensionsV1beta1DeploymentConditionType =
  ExtensionsV1beta1DeploymentCondition
  { extensionsV1beta1DeploymentConditionLastTransitionTime = Nothing
  , extensionsV1beta1DeploymentConditionLastUpdateTime = Nothing
  , extensionsV1beta1DeploymentConditionMessage = Nothing
  , extensionsV1beta1DeploymentConditionReason = Nothing
  , extensionsV1beta1DeploymentConditionStatus
  , extensionsV1beta1DeploymentConditionType
  }

-- ** ExtensionsV1beta1DeploymentList
-- | ExtensionsV1beta1DeploymentList
-- DeploymentList is a list of Deployments.
data ExtensionsV1beta1DeploymentList = ExtensionsV1beta1DeploymentList
  { extensionsV1beta1DeploymentListApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , extensionsV1beta1DeploymentListItems :: !([ExtensionsV1beta1Deployment]) -- ^ /Required/ "items" - Items is the list of Deployments.
  , extensionsV1beta1DeploymentListKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , extensionsV1beta1DeploymentListMetadata :: !(Maybe V1ListMeta) -- ^ "metadata"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1DeploymentList
instance A.FromJSON ExtensionsV1beta1DeploymentList where
  parseJSON = A.withObject "ExtensionsV1beta1DeploymentList" $ \o ->
    ExtensionsV1beta1DeploymentList
      <$> (o .:? "apiVersion")
      <*> (o .:  "items")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")

-- | ToJSON ExtensionsV1beta1DeploymentList
instance A.ToJSON ExtensionsV1beta1DeploymentList where
  toJSON ExtensionsV1beta1DeploymentList {..} =
   _omitNulls
      [ "apiVersion" .= extensionsV1beta1DeploymentListApiVersion
      , "items" .= extensionsV1beta1DeploymentListItems
      , "kind" .= extensionsV1beta1DeploymentListKind
      , "metadata" .= extensionsV1beta1DeploymentListMetadata
      ]


-- | Construct a value of type 'ExtensionsV1beta1DeploymentList' (by applying it's required fields, if any)
mkExtensionsV1beta1DeploymentList
  :: [ExtensionsV1beta1Deployment] -- ^ 'extensionsV1beta1DeploymentListItems': Items is the list of Deployments.
  -> ExtensionsV1beta1DeploymentList
mkExtensionsV1beta1DeploymentList extensionsV1beta1DeploymentListItems =
  ExtensionsV1beta1DeploymentList
  { extensionsV1beta1DeploymentListApiVersion = Nothing
  , extensionsV1beta1DeploymentListItems
  , extensionsV1beta1DeploymentListKind = Nothing
  , extensionsV1beta1DeploymentListMetadata = Nothing
  }

-- ** ExtensionsV1beta1DeploymentRollback
-- | ExtensionsV1beta1DeploymentRollback
-- DEPRECATED. DeploymentRollback stores the information required to rollback a deployment.
data ExtensionsV1beta1DeploymentRollback = ExtensionsV1beta1DeploymentRollback
  { extensionsV1beta1DeploymentRollbackApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , extensionsV1beta1DeploymentRollbackKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , extensionsV1beta1DeploymentRollbackName :: !(Text) -- ^ /Required/ "name" - Required: This must match the Name of a deployment.
  , extensionsV1beta1DeploymentRollbackRollbackTo :: !(ExtensionsV1beta1RollbackConfig) -- ^ /Required/ "rollbackTo"
  , extensionsV1beta1DeploymentRollbackUpdatedAnnotations :: !(Maybe (Map.Map String Text)) -- ^ "updatedAnnotations" - The annotations to be updated to a deployment
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1DeploymentRollback
instance A.FromJSON ExtensionsV1beta1DeploymentRollback where
  parseJSON = A.withObject "ExtensionsV1beta1DeploymentRollback" $ \o ->
    ExtensionsV1beta1DeploymentRollback
      <$> (o .:? "apiVersion")
      <*> (o .:? "kind")
      <*> (o .:  "name")
      <*> (o .:  "rollbackTo")
      <*> (o .:? "updatedAnnotations")

-- | ToJSON ExtensionsV1beta1DeploymentRollback
instance A.ToJSON ExtensionsV1beta1DeploymentRollback where
  toJSON ExtensionsV1beta1DeploymentRollback {..} =
   _omitNulls
      [ "apiVersion" .= extensionsV1beta1DeploymentRollbackApiVersion
      , "kind" .= extensionsV1beta1DeploymentRollbackKind
      , "name" .= extensionsV1beta1DeploymentRollbackName
      , "rollbackTo" .= extensionsV1beta1DeploymentRollbackRollbackTo
      , "updatedAnnotations" .= extensionsV1beta1DeploymentRollbackUpdatedAnnotations
      ]


-- | Construct a value of type 'ExtensionsV1beta1DeploymentRollback' (by applying it's required fields, if any)
mkExtensionsV1beta1DeploymentRollback
  :: Text -- ^ 'extensionsV1beta1DeploymentRollbackName': Required: This must match the Name of a deployment.
  -> ExtensionsV1beta1RollbackConfig -- ^ 'extensionsV1beta1DeploymentRollbackRollbackTo' 
  -> ExtensionsV1beta1DeploymentRollback
mkExtensionsV1beta1DeploymentRollback extensionsV1beta1DeploymentRollbackName extensionsV1beta1DeploymentRollbackRollbackTo =
  ExtensionsV1beta1DeploymentRollback
  { extensionsV1beta1DeploymentRollbackApiVersion = Nothing
  , extensionsV1beta1DeploymentRollbackKind = Nothing
  , extensionsV1beta1DeploymentRollbackName
  , extensionsV1beta1DeploymentRollbackRollbackTo
  , extensionsV1beta1DeploymentRollbackUpdatedAnnotations = Nothing
  }

-- ** ExtensionsV1beta1DeploymentSpec
-- | ExtensionsV1beta1DeploymentSpec
-- DeploymentSpec is the specification of the desired behavior of the Deployment.
data ExtensionsV1beta1DeploymentSpec = ExtensionsV1beta1DeploymentSpec
  { extensionsV1beta1DeploymentSpecMinReadySeconds :: !(Maybe Int) -- ^ "minReadySeconds" - Minimum number of seconds for which a newly created pod should be ready without any of its container crashing, for it to be considered available. Defaults to 0 (pod will be considered available as soon as it is ready)
  , extensionsV1beta1DeploymentSpecPaused :: !(Maybe Bool) -- ^ "paused" - Indicates that the deployment is paused and will not be processed by the deployment controller.
  , extensionsV1beta1DeploymentSpecProgressDeadlineSeconds :: !(Maybe Int) -- ^ "progressDeadlineSeconds" - The maximum time in seconds for a deployment to make progress before it is considered to be failed. The deployment controller will continue to process failed deployments and a condition with a ProgressDeadlineExceeded reason will be surfaced in the deployment status. Note that progress will not be estimated during the time a deployment is paused. This is set to the max value of int32 (i.e. 2147483647) by default, which means \&quot;no deadline\&quot;.
  , extensionsV1beta1DeploymentSpecReplicas :: !(Maybe Int) -- ^ "replicas" - Number of desired pods. This is a pointer to distinguish between explicit zero and not specified. Defaults to 1.
  , extensionsV1beta1DeploymentSpecRevisionHistoryLimit :: !(Maybe Int) -- ^ "revisionHistoryLimit" - The number of old ReplicaSets to retain to allow rollback. This is a pointer to distinguish between explicit zero and not specified. This is set to the max value of int32 (i.e. 2147483647) by default, which means \&quot;retaining all old RelicaSets\&quot;.
  , extensionsV1beta1DeploymentSpecRollbackTo :: !(Maybe ExtensionsV1beta1RollbackConfig) -- ^ "rollbackTo"
  , extensionsV1beta1DeploymentSpecSelector :: !(Maybe V1LabelSelector) -- ^ "selector"
  , extensionsV1beta1DeploymentSpecStrategy :: !(Maybe ExtensionsV1beta1DeploymentStrategy) -- ^ "strategy"
  , extensionsV1beta1DeploymentSpecTemplate :: !(V1PodTemplateSpec) -- ^ /Required/ "template"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1DeploymentSpec
instance A.FromJSON ExtensionsV1beta1DeploymentSpec where
  parseJSON = A.withObject "ExtensionsV1beta1DeploymentSpec" $ \o ->
    ExtensionsV1beta1DeploymentSpec
      <$> (o .:? "minReadySeconds")
      <*> (o .:? "paused")
      <*> (o .:? "progressDeadlineSeconds")
      <*> (o .:? "replicas")
      <*> (o .:? "revisionHistoryLimit")
      <*> (o .:? "rollbackTo")
      <*> (o .:? "selector")
      <*> (o .:? "strategy")
      <*> (o .:  "template")

-- | ToJSON ExtensionsV1beta1DeploymentSpec
instance A.ToJSON ExtensionsV1beta1DeploymentSpec where
  toJSON ExtensionsV1beta1DeploymentSpec {..} =
   _omitNulls
      [ "minReadySeconds" .= extensionsV1beta1DeploymentSpecMinReadySeconds
      , "paused" .= extensionsV1beta1DeploymentSpecPaused
      , "progressDeadlineSeconds" .= extensionsV1beta1DeploymentSpecProgressDeadlineSeconds
      , "replicas" .= extensionsV1beta1DeploymentSpecReplicas
      , "revisionHistoryLimit" .= extensionsV1beta1DeploymentSpecRevisionHistoryLimit
      , "rollbackTo" .= extensionsV1beta1DeploymentSpecRollbackTo
      , "selector" .= extensionsV1beta1DeploymentSpecSelector
      , "strategy" .= extensionsV1beta1DeploymentSpecStrategy
      , "template" .= extensionsV1beta1DeploymentSpecTemplate
      ]


-- | Construct a value of type 'ExtensionsV1beta1DeploymentSpec' (by applying it's required fields, if any)
mkExtensionsV1beta1DeploymentSpec
  :: V1PodTemplateSpec -- ^ 'extensionsV1beta1DeploymentSpecTemplate' 
  -> ExtensionsV1beta1DeploymentSpec
mkExtensionsV1beta1DeploymentSpec extensionsV1beta1DeploymentSpecTemplate =
  ExtensionsV1beta1DeploymentSpec
  { extensionsV1beta1DeploymentSpecMinReadySeconds = Nothing
  , extensionsV1beta1DeploymentSpecPaused = Nothing
  , extensionsV1beta1DeploymentSpecProgressDeadlineSeconds = Nothing
  , extensionsV1beta1DeploymentSpecReplicas = Nothing
  , extensionsV1beta1DeploymentSpecRevisionHistoryLimit = Nothing
  , extensionsV1beta1DeploymentSpecRollbackTo = Nothing
  , extensionsV1beta1DeploymentSpecSelector = Nothing
  , extensionsV1beta1DeploymentSpecStrategy = Nothing
  , extensionsV1beta1DeploymentSpecTemplate
  }

-- ** ExtensionsV1beta1DeploymentStatus
-- | ExtensionsV1beta1DeploymentStatus
-- DeploymentStatus is the most recently observed status of the Deployment.
data ExtensionsV1beta1DeploymentStatus = ExtensionsV1beta1DeploymentStatus
  { extensionsV1beta1DeploymentStatusAvailableReplicas :: !(Maybe Int) -- ^ "availableReplicas" - Total number of available pods (ready for at least minReadySeconds) targeted by this deployment.
  , extensionsV1beta1DeploymentStatusCollisionCount :: !(Maybe Int) -- ^ "collisionCount" - Count of hash collisions for the Deployment. The Deployment controller uses this field as a collision avoidance mechanism when it needs to create the name for the newest ReplicaSet.
  , extensionsV1beta1DeploymentStatusConditions :: !(Maybe [ExtensionsV1beta1DeploymentCondition]) -- ^ "conditions" - Represents the latest available observations of a deployment&#39;s current state.
  , extensionsV1beta1DeploymentStatusObservedGeneration :: !(Maybe Integer) -- ^ "observedGeneration" - The generation observed by the deployment controller.
  , extensionsV1beta1DeploymentStatusReadyReplicas :: !(Maybe Int) -- ^ "readyReplicas" - Total number of ready pods targeted by this deployment.
  , extensionsV1beta1DeploymentStatusReplicas :: !(Maybe Int) -- ^ "replicas" - Total number of non-terminated pods targeted by this deployment (their labels match the selector).
  , extensionsV1beta1DeploymentStatusUnavailableReplicas :: !(Maybe Int) -- ^ "unavailableReplicas" - Total number of unavailable pods targeted by this deployment. This is the total number of pods that are still required for the deployment to have 100% available capacity. They may either be pods that are running but not yet available or pods that still have not been created.
  , extensionsV1beta1DeploymentStatusUpdatedReplicas :: !(Maybe Int) -- ^ "updatedReplicas" - Total number of non-terminated pods targeted by this deployment that have the desired template spec.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1DeploymentStatus
instance A.FromJSON ExtensionsV1beta1DeploymentStatus where
  parseJSON = A.withObject "ExtensionsV1beta1DeploymentStatus" $ \o ->
    ExtensionsV1beta1DeploymentStatus
      <$> (o .:? "availableReplicas")
      <*> (o .:? "collisionCount")
      <*> (o .:? "conditions")
      <*> (o .:? "observedGeneration")
      <*> (o .:? "readyReplicas")
      <*> (o .:? "replicas")
      <*> (o .:? "unavailableReplicas")
      <*> (o .:? "updatedReplicas")

-- | ToJSON ExtensionsV1beta1DeploymentStatus
instance A.ToJSON ExtensionsV1beta1DeploymentStatus where
  toJSON ExtensionsV1beta1DeploymentStatus {..} =
   _omitNulls
      [ "availableReplicas" .= extensionsV1beta1DeploymentStatusAvailableReplicas
      , "collisionCount" .= extensionsV1beta1DeploymentStatusCollisionCount
      , "conditions" .= extensionsV1beta1DeploymentStatusConditions
      , "observedGeneration" .= extensionsV1beta1DeploymentStatusObservedGeneration
      , "readyReplicas" .= extensionsV1beta1DeploymentStatusReadyReplicas
      , "replicas" .= extensionsV1beta1DeploymentStatusReplicas
      , "unavailableReplicas" .= extensionsV1beta1DeploymentStatusUnavailableReplicas
      , "updatedReplicas" .= extensionsV1beta1DeploymentStatusUpdatedReplicas
      ]


-- | Construct a value of type 'ExtensionsV1beta1DeploymentStatus' (by applying it's required fields, if any)
mkExtensionsV1beta1DeploymentStatus
  :: ExtensionsV1beta1DeploymentStatus
mkExtensionsV1beta1DeploymentStatus =
  ExtensionsV1beta1DeploymentStatus
  { extensionsV1beta1DeploymentStatusAvailableReplicas = Nothing
  , extensionsV1beta1DeploymentStatusCollisionCount = Nothing
  , extensionsV1beta1DeploymentStatusConditions = Nothing
  , extensionsV1beta1DeploymentStatusObservedGeneration = Nothing
  , extensionsV1beta1DeploymentStatusReadyReplicas = Nothing
  , extensionsV1beta1DeploymentStatusReplicas = Nothing
  , extensionsV1beta1DeploymentStatusUnavailableReplicas = Nothing
  , extensionsV1beta1DeploymentStatusUpdatedReplicas = Nothing
  }

-- ** ExtensionsV1beta1DeploymentStrategy
-- | ExtensionsV1beta1DeploymentStrategy
-- DeploymentStrategy describes how to replace existing pods with new ones.
data ExtensionsV1beta1DeploymentStrategy = ExtensionsV1beta1DeploymentStrategy
  { extensionsV1beta1DeploymentStrategyRollingUpdate :: !(Maybe ExtensionsV1beta1RollingUpdateDeployment) -- ^ "rollingUpdate"
  , extensionsV1beta1DeploymentStrategyType :: !(Maybe Text) -- ^ "type" - Type of deployment. Can be \&quot;Recreate\&quot; or \&quot;RollingUpdate\&quot;. Default is RollingUpdate.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1DeploymentStrategy
instance A.FromJSON ExtensionsV1beta1DeploymentStrategy where
  parseJSON = A.withObject "ExtensionsV1beta1DeploymentStrategy" $ \o ->
    ExtensionsV1beta1DeploymentStrategy
      <$> (o .:? "rollingUpdate")
      <*> (o .:? "type")

-- | ToJSON ExtensionsV1beta1DeploymentStrategy
instance A.ToJSON ExtensionsV1beta1DeploymentStrategy where
  toJSON ExtensionsV1beta1DeploymentStrategy {..} =
   _omitNulls
      [ "rollingUpdate" .= extensionsV1beta1DeploymentStrategyRollingUpdate
      , "type" .= extensionsV1beta1DeploymentStrategyType
      ]


-- | Construct a value of type 'ExtensionsV1beta1DeploymentStrategy' (by applying it's required fields, if any)
mkExtensionsV1beta1DeploymentStrategy
  :: ExtensionsV1beta1DeploymentStrategy
mkExtensionsV1beta1DeploymentStrategy =
  ExtensionsV1beta1DeploymentStrategy
  { extensionsV1beta1DeploymentStrategyRollingUpdate = Nothing
  , extensionsV1beta1DeploymentStrategyType = Nothing
  }

-- ** ExtensionsV1beta1FSGroupStrategyOptions
-- | ExtensionsV1beta1FSGroupStrategyOptions
-- FSGroupStrategyOptions defines the strategy type and options used to create the strategy. Deprecated: use FSGroupStrategyOptions from policy API Group instead.
data ExtensionsV1beta1FSGroupStrategyOptions = ExtensionsV1beta1FSGroupStrategyOptions
  { extensionsV1beta1FSGroupStrategyOptionsRanges :: !(Maybe [ExtensionsV1beta1IDRange]) -- ^ "ranges" - ranges are the allowed ranges of fs groups.  If you would like to force a single fs group then supply a single range with the same start and end. Required for MustRunAs.
  , extensionsV1beta1FSGroupStrategyOptionsRule :: !(Maybe Text) -- ^ "rule" - rule is the strategy that will dictate what FSGroup is used in the SecurityContext.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1FSGroupStrategyOptions
instance A.FromJSON ExtensionsV1beta1FSGroupStrategyOptions where
  parseJSON = A.withObject "ExtensionsV1beta1FSGroupStrategyOptions" $ \o ->
    ExtensionsV1beta1FSGroupStrategyOptions
      <$> (o .:? "ranges")
      <*> (o .:? "rule")

-- | ToJSON ExtensionsV1beta1FSGroupStrategyOptions
instance A.ToJSON ExtensionsV1beta1FSGroupStrategyOptions where
  toJSON ExtensionsV1beta1FSGroupStrategyOptions {..} =
   _omitNulls
      [ "ranges" .= extensionsV1beta1FSGroupStrategyOptionsRanges
      , "rule" .= extensionsV1beta1FSGroupStrategyOptionsRule
      ]


-- | Construct a value of type 'ExtensionsV1beta1FSGroupStrategyOptions' (by applying it's required fields, if any)
mkExtensionsV1beta1FSGroupStrategyOptions
  :: ExtensionsV1beta1FSGroupStrategyOptions
mkExtensionsV1beta1FSGroupStrategyOptions =
  ExtensionsV1beta1FSGroupStrategyOptions
  { extensionsV1beta1FSGroupStrategyOptionsRanges = Nothing
  , extensionsV1beta1FSGroupStrategyOptionsRule = Nothing
  }

-- ** ExtensionsV1beta1HTTPIngressPath
-- | ExtensionsV1beta1HTTPIngressPath
-- HTTPIngressPath associates a path regex with a backend. Incoming urls matching the path are forwarded to the backend.
data ExtensionsV1beta1HTTPIngressPath = ExtensionsV1beta1HTTPIngressPath
  { extensionsV1beta1HTTPIngressPathBackend :: !(ExtensionsV1beta1IngressBackend) -- ^ /Required/ "backend"
  , extensionsV1beta1HTTPIngressPathPath :: !(Maybe Text) -- ^ "path" - Path is an extended POSIX regex as defined by IEEE Std 1003.1, (i.e this follows the egrep/unix syntax, not the perl syntax) matched against the path of an incoming request. Currently it can contain characters disallowed from the conventional \&quot;path\&quot; part of a URL as defined by RFC 3986. Paths must begin with a &#39;/&#39;. If unspecified, the path defaults to a catch all sending traffic to the backend.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1HTTPIngressPath
instance A.FromJSON ExtensionsV1beta1HTTPIngressPath where
  parseJSON = A.withObject "ExtensionsV1beta1HTTPIngressPath" $ \o ->
    ExtensionsV1beta1HTTPIngressPath
      <$> (o .:  "backend")
      <*> (o .:? "path")

-- | ToJSON ExtensionsV1beta1HTTPIngressPath
instance A.ToJSON ExtensionsV1beta1HTTPIngressPath where
  toJSON ExtensionsV1beta1HTTPIngressPath {..} =
   _omitNulls
      [ "backend" .= extensionsV1beta1HTTPIngressPathBackend
      , "path" .= extensionsV1beta1HTTPIngressPathPath
      ]


-- | Construct a value of type 'ExtensionsV1beta1HTTPIngressPath' (by applying it's required fields, if any)
mkExtensionsV1beta1HTTPIngressPath
  :: ExtensionsV1beta1IngressBackend -- ^ 'extensionsV1beta1HTTPIngressPathBackend' 
  -> ExtensionsV1beta1HTTPIngressPath
mkExtensionsV1beta1HTTPIngressPath extensionsV1beta1HTTPIngressPathBackend =
  ExtensionsV1beta1HTTPIngressPath
  { extensionsV1beta1HTTPIngressPathBackend
  , extensionsV1beta1HTTPIngressPathPath = Nothing
  }

-- ** ExtensionsV1beta1HTTPIngressRuleValue
-- | ExtensionsV1beta1HTTPIngressRuleValue
-- HTTPIngressRuleValue is a list of http selectors pointing to backends. In the example: http://<host>/<path>?<searchpart> -> backend where where parts of the url correspond to RFC 3986, this resource will be used to match against everything after the last '/' and before the first '?' or '#'.
data ExtensionsV1beta1HTTPIngressRuleValue = ExtensionsV1beta1HTTPIngressRuleValue
  { extensionsV1beta1HTTPIngressRuleValuePaths :: !([ExtensionsV1beta1HTTPIngressPath]) -- ^ /Required/ "paths" - A collection of paths that map requests to backends.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1HTTPIngressRuleValue
instance A.FromJSON ExtensionsV1beta1HTTPIngressRuleValue where
  parseJSON = A.withObject "ExtensionsV1beta1HTTPIngressRuleValue" $ \o ->
    ExtensionsV1beta1HTTPIngressRuleValue
      <$> (o .:  "paths")

-- | ToJSON ExtensionsV1beta1HTTPIngressRuleValue
instance A.ToJSON ExtensionsV1beta1HTTPIngressRuleValue where
  toJSON ExtensionsV1beta1HTTPIngressRuleValue {..} =
   _omitNulls
      [ "paths" .= extensionsV1beta1HTTPIngressRuleValuePaths
      ]


-- | Construct a value of type 'ExtensionsV1beta1HTTPIngressRuleValue' (by applying it's required fields, if any)
mkExtensionsV1beta1HTTPIngressRuleValue
  :: [ExtensionsV1beta1HTTPIngressPath] -- ^ 'extensionsV1beta1HTTPIngressRuleValuePaths': A collection of paths that map requests to backends.
  -> ExtensionsV1beta1HTTPIngressRuleValue
mkExtensionsV1beta1HTTPIngressRuleValue extensionsV1beta1HTTPIngressRuleValuePaths =
  ExtensionsV1beta1HTTPIngressRuleValue
  { extensionsV1beta1HTTPIngressRuleValuePaths
  }

-- ** ExtensionsV1beta1HostPortRange
-- | ExtensionsV1beta1HostPortRange
-- HostPortRange defines a range of host ports that will be enabled by a policy for pods to use.  It requires both the start and end to be defined. Deprecated: use HostPortRange from policy API Group instead.
data ExtensionsV1beta1HostPortRange = ExtensionsV1beta1HostPortRange
  { extensionsV1beta1HostPortRangeMax :: !(Int) -- ^ /Required/ "max" - max is the end of the range, inclusive.
  , extensionsV1beta1HostPortRangeMin :: !(Int) -- ^ /Required/ "min" - min is the start of the range, inclusive.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1HostPortRange
instance A.FromJSON ExtensionsV1beta1HostPortRange where
  parseJSON = A.withObject "ExtensionsV1beta1HostPortRange" $ \o ->
    ExtensionsV1beta1HostPortRange
      <$> (o .:  "max")
      <*> (o .:  "min")

-- | ToJSON ExtensionsV1beta1HostPortRange
instance A.ToJSON ExtensionsV1beta1HostPortRange where
  toJSON ExtensionsV1beta1HostPortRange {..} =
   _omitNulls
      [ "max" .= extensionsV1beta1HostPortRangeMax
      , "min" .= extensionsV1beta1HostPortRangeMin
      ]


-- | Construct a value of type 'ExtensionsV1beta1HostPortRange' (by applying it's required fields, if any)
mkExtensionsV1beta1HostPortRange
  :: Int -- ^ 'extensionsV1beta1HostPortRangeMax': max is the end of the range, inclusive.
  -> Int -- ^ 'extensionsV1beta1HostPortRangeMin': min is the start of the range, inclusive.
  -> ExtensionsV1beta1HostPortRange
mkExtensionsV1beta1HostPortRange extensionsV1beta1HostPortRangeMax extensionsV1beta1HostPortRangeMin =
  ExtensionsV1beta1HostPortRange
  { extensionsV1beta1HostPortRangeMax
  , extensionsV1beta1HostPortRangeMin
  }

-- ** ExtensionsV1beta1IDRange
-- | ExtensionsV1beta1IDRange
-- IDRange provides a min/max of an allowed range of IDs. Deprecated: use IDRange from policy API Group instead.
data ExtensionsV1beta1IDRange = ExtensionsV1beta1IDRange
  { extensionsV1beta1IDRangeMax :: !(Integer) -- ^ /Required/ "max" - max is the end of the range, inclusive.
  , extensionsV1beta1IDRangeMin :: !(Integer) -- ^ /Required/ "min" - min is the start of the range, inclusive.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1IDRange
instance A.FromJSON ExtensionsV1beta1IDRange where
  parseJSON = A.withObject "ExtensionsV1beta1IDRange" $ \o ->
    ExtensionsV1beta1IDRange
      <$> (o .:  "max")
      <*> (o .:  "min")

-- | ToJSON ExtensionsV1beta1IDRange
instance A.ToJSON ExtensionsV1beta1IDRange where
  toJSON ExtensionsV1beta1IDRange {..} =
   _omitNulls
      [ "max" .= extensionsV1beta1IDRangeMax
      , "min" .= extensionsV1beta1IDRangeMin
      ]


-- | Construct a value of type 'ExtensionsV1beta1IDRange' (by applying it's required fields, if any)
mkExtensionsV1beta1IDRange
  :: Integer -- ^ 'extensionsV1beta1IDRangeMax': max is the end of the range, inclusive.
  -> Integer -- ^ 'extensionsV1beta1IDRangeMin': min is the start of the range, inclusive.
  -> ExtensionsV1beta1IDRange
mkExtensionsV1beta1IDRange extensionsV1beta1IDRangeMax extensionsV1beta1IDRangeMin =
  ExtensionsV1beta1IDRange
  { extensionsV1beta1IDRangeMax
  , extensionsV1beta1IDRangeMin
  }

-- ** ExtensionsV1beta1Ingress
-- | ExtensionsV1beta1Ingress
-- Ingress is a collection of rules that allow inbound connections to reach the endpoints defined by a backend. An Ingress can be configured to give services externally-reachable urls, load balance traffic, terminate SSL, offer name based virtual hosting etc. DEPRECATED - This group version of Ingress is deprecated by networking.k8s.io/v1beta1 Ingress. See the release notes for more information.
data ExtensionsV1beta1Ingress = ExtensionsV1beta1Ingress
  { extensionsV1beta1IngressApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , extensionsV1beta1IngressKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , extensionsV1beta1IngressMetadata :: !(Maybe V1ObjectMeta) -- ^ "metadata"
  , extensionsV1beta1IngressSpec :: !(Maybe ExtensionsV1beta1IngressSpec) -- ^ "spec"
  , extensionsV1beta1IngressStatus :: !(Maybe ExtensionsV1beta1IngressStatus) -- ^ "status"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1Ingress
instance A.FromJSON ExtensionsV1beta1Ingress where
  parseJSON = A.withObject "ExtensionsV1beta1Ingress" $ \o ->
    ExtensionsV1beta1Ingress
      <$> (o .:? "apiVersion")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")
      <*> (o .:? "spec")
      <*> (o .:? "status")

-- | ToJSON ExtensionsV1beta1Ingress
instance A.ToJSON ExtensionsV1beta1Ingress where
  toJSON ExtensionsV1beta1Ingress {..} =
   _omitNulls
      [ "apiVersion" .= extensionsV1beta1IngressApiVersion
      , "kind" .= extensionsV1beta1IngressKind
      , "metadata" .= extensionsV1beta1IngressMetadata
      , "spec" .= extensionsV1beta1IngressSpec
      , "status" .= extensionsV1beta1IngressStatus
      ]


-- | Construct a value of type 'ExtensionsV1beta1Ingress' (by applying it's required fields, if any)
mkExtensionsV1beta1Ingress
  :: ExtensionsV1beta1Ingress
mkExtensionsV1beta1Ingress =
  ExtensionsV1beta1Ingress
  { extensionsV1beta1IngressApiVersion = Nothing
  , extensionsV1beta1IngressKind = Nothing
  , extensionsV1beta1IngressMetadata = Nothing
  , extensionsV1beta1IngressSpec = Nothing
  , extensionsV1beta1IngressStatus = Nothing
  }

-- ** ExtensionsV1beta1IngressBackend
-- | ExtensionsV1beta1IngressBackend
-- IngressBackend describes all endpoints for a given service and port.
data ExtensionsV1beta1IngressBackend = ExtensionsV1beta1IngressBackend
  { extensionsV1beta1IngressBackendServiceName :: !(Text) -- ^ /Required/ "serviceName" - Specifies the name of the referenced service.
  , extensionsV1beta1IngressBackendServicePort :: !(IntOrString) -- ^ /Required/ "servicePort"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1IngressBackend
instance A.FromJSON ExtensionsV1beta1IngressBackend where
  parseJSON = A.withObject "ExtensionsV1beta1IngressBackend" $ \o ->
    ExtensionsV1beta1IngressBackend
      <$> (o .:  "serviceName")
      <*> (o .:  "servicePort")

-- | ToJSON ExtensionsV1beta1IngressBackend
instance A.ToJSON ExtensionsV1beta1IngressBackend where
  toJSON ExtensionsV1beta1IngressBackend {..} =
   _omitNulls
      [ "serviceName" .= extensionsV1beta1IngressBackendServiceName
      , "servicePort" .= extensionsV1beta1IngressBackendServicePort
      ]


-- | Construct a value of type 'ExtensionsV1beta1IngressBackend' (by applying it's required fields, if any)
mkExtensionsV1beta1IngressBackend
  :: Text -- ^ 'extensionsV1beta1IngressBackendServiceName': Specifies the name of the referenced service.
  -> IntOrString -- ^ 'extensionsV1beta1IngressBackendServicePort' 
  -> ExtensionsV1beta1IngressBackend
mkExtensionsV1beta1IngressBackend extensionsV1beta1IngressBackendServiceName extensionsV1beta1IngressBackendServicePort =
  ExtensionsV1beta1IngressBackend
  { extensionsV1beta1IngressBackendServiceName
  , extensionsV1beta1IngressBackendServicePort
  }

-- ** ExtensionsV1beta1IngressList
-- | ExtensionsV1beta1IngressList
-- IngressList is a collection of Ingress.
data ExtensionsV1beta1IngressList = ExtensionsV1beta1IngressList
  { extensionsV1beta1IngressListApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , extensionsV1beta1IngressListItems :: !([ExtensionsV1beta1Ingress]) -- ^ /Required/ "items" - Items is the list of Ingress.
  , extensionsV1beta1IngressListKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , extensionsV1beta1IngressListMetadata :: !(Maybe V1ListMeta) -- ^ "metadata"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1IngressList
instance A.FromJSON ExtensionsV1beta1IngressList where
  parseJSON = A.withObject "ExtensionsV1beta1IngressList" $ \o ->
    ExtensionsV1beta1IngressList
      <$> (o .:? "apiVersion")
      <*> (o .:  "items")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")

-- | ToJSON ExtensionsV1beta1IngressList
instance A.ToJSON ExtensionsV1beta1IngressList where
  toJSON ExtensionsV1beta1IngressList {..} =
   _omitNulls
      [ "apiVersion" .= extensionsV1beta1IngressListApiVersion
      , "items" .= extensionsV1beta1IngressListItems
      , "kind" .= extensionsV1beta1IngressListKind
      , "metadata" .= extensionsV1beta1IngressListMetadata
      ]


-- | Construct a value of type 'ExtensionsV1beta1IngressList' (by applying it's required fields, if any)
mkExtensionsV1beta1IngressList
  :: [ExtensionsV1beta1Ingress] -- ^ 'extensionsV1beta1IngressListItems': Items is the list of Ingress.
  -> ExtensionsV1beta1IngressList
mkExtensionsV1beta1IngressList extensionsV1beta1IngressListItems =
  ExtensionsV1beta1IngressList
  { extensionsV1beta1IngressListApiVersion = Nothing
  , extensionsV1beta1IngressListItems
  , extensionsV1beta1IngressListKind = Nothing
  , extensionsV1beta1IngressListMetadata = Nothing
  }

-- ** ExtensionsV1beta1IngressRule
-- | ExtensionsV1beta1IngressRule
-- IngressRule represents the rules mapping the paths under a specified host to the related backend services. Incoming requests are first evaluated for a host match, then routed to the backend associated with the matching IngressRuleValue.
data ExtensionsV1beta1IngressRule = ExtensionsV1beta1IngressRule
  { extensionsV1beta1IngressRuleHost :: !(Maybe Text) -- ^ "host" - Host is the fully qualified domain name of a network host, as defined by RFC 3986. Note the following deviations from the \&quot;host\&quot; part of the URI as defined in the RFC: 1. IPs are not allowed. Currently an IngressRuleValue can only apply to the    IP in the Spec of the parent Ingress. 2. The &#x60;:&#x60; delimiter is not respected because ports are not allowed.    Currently the port of an Ingress is implicitly :80 for http and    :443 for https. Both these may change in the future. Incoming requests are matched against the host before the IngressRuleValue. If the host is unspecified, the Ingress routes all traffic based on the specified IngressRuleValue.
  , extensionsV1beta1IngressRuleHttp :: !(Maybe ExtensionsV1beta1HTTPIngressRuleValue) -- ^ "http"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1IngressRule
instance A.FromJSON ExtensionsV1beta1IngressRule where
  parseJSON = A.withObject "ExtensionsV1beta1IngressRule" $ \o ->
    ExtensionsV1beta1IngressRule
      <$> (o .:? "host")
      <*> (o .:? "http")

-- | ToJSON ExtensionsV1beta1IngressRule
instance A.ToJSON ExtensionsV1beta1IngressRule where
  toJSON ExtensionsV1beta1IngressRule {..} =
   _omitNulls
      [ "host" .= extensionsV1beta1IngressRuleHost
      , "http" .= extensionsV1beta1IngressRuleHttp
      ]


-- | Construct a value of type 'ExtensionsV1beta1IngressRule' (by applying it's required fields, if any)
mkExtensionsV1beta1IngressRule
  :: ExtensionsV1beta1IngressRule
mkExtensionsV1beta1IngressRule =
  ExtensionsV1beta1IngressRule
  { extensionsV1beta1IngressRuleHost = Nothing
  , extensionsV1beta1IngressRuleHttp = Nothing
  }

-- ** ExtensionsV1beta1IngressSpec
-- | ExtensionsV1beta1IngressSpec
-- IngressSpec describes the Ingress the user wishes to exist.
data ExtensionsV1beta1IngressSpec = ExtensionsV1beta1IngressSpec
  { extensionsV1beta1IngressSpecBackend :: !(Maybe ExtensionsV1beta1IngressBackend) -- ^ "backend"
  , extensionsV1beta1IngressSpecRules :: !(Maybe [ExtensionsV1beta1IngressRule]) -- ^ "rules" - A list of host rules used to configure the Ingress. If unspecified, or no rule matches, all traffic is sent to the default backend.
  , extensionsV1beta1IngressSpecTls :: !(Maybe [ExtensionsV1beta1IngressTLS]) -- ^ "tls" - TLS configuration. Currently the Ingress only supports a single TLS port, 443. If multiple members of this list specify different hosts, they will be multiplexed on the same port according to the hostname specified through the SNI TLS extension, if the ingress controller fulfilling the ingress supports SNI.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1IngressSpec
instance A.FromJSON ExtensionsV1beta1IngressSpec where
  parseJSON = A.withObject "ExtensionsV1beta1IngressSpec" $ \o ->
    ExtensionsV1beta1IngressSpec
      <$> (o .:? "backend")
      <*> (o .:? "rules")
      <*> (o .:? "tls")

-- | ToJSON ExtensionsV1beta1IngressSpec
instance A.ToJSON ExtensionsV1beta1IngressSpec where
  toJSON ExtensionsV1beta1IngressSpec {..} =
   _omitNulls
      [ "backend" .= extensionsV1beta1IngressSpecBackend
      , "rules" .= extensionsV1beta1IngressSpecRules
      , "tls" .= extensionsV1beta1IngressSpecTls
      ]


-- | Construct a value of type 'ExtensionsV1beta1IngressSpec' (by applying it's required fields, if any)
mkExtensionsV1beta1IngressSpec
  :: ExtensionsV1beta1IngressSpec
mkExtensionsV1beta1IngressSpec =
  ExtensionsV1beta1IngressSpec
  { extensionsV1beta1IngressSpecBackend = Nothing
  , extensionsV1beta1IngressSpecRules = Nothing
  , extensionsV1beta1IngressSpecTls = Nothing
  }

-- ** ExtensionsV1beta1IngressStatus
-- | ExtensionsV1beta1IngressStatus
-- IngressStatus describe the current state of the Ingress.
data ExtensionsV1beta1IngressStatus = ExtensionsV1beta1IngressStatus
  { extensionsV1beta1IngressStatusLoadBalancer :: !(Maybe V1LoadBalancerStatus) -- ^ "loadBalancer"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1IngressStatus
instance A.FromJSON ExtensionsV1beta1IngressStatus where
  parseJSON = A.withObject "ExtensionsV1beta1IngressStatus" $ \o ->
    ExtensionsV1beta1IngressStatus
      <$> (o .:? "loadBalancer")

-- | ToJSON ExtensionsV1beta1IngressStatus
instance A.ToJSON ExtensionsV1beta1IngressStatus where
  toJSON ExtensionsV1beta1IngressStatus {..} =
   _omitNulls
      [ "loadBalancer" .= extensionsV1beta1IngressStatusLoadBalancer
      ]


-- | Construct a value of type 'ExtensionsV1beta1IngressStatus' (by applying it's required fields, if any)
mkExtensionsV1beta1IngressStatus
  :: ExtensionsV1beta1IngressStatus
mkExtensionsV1beta1IngressStatus =
  ExtensionsV1beta1IngressStatus
  { extensionsV1beta1IngressStatusLoadBalancer = Nothing
  }

-- ** ExtensionsV1beta1IngressTLS
-- | ExtensionsV1beta1IngressTLS
-- IngressTLS describes the transport layer security associated with an Ingress.
data ExtensionsV1beta1IngressTLS = ExtensionsV1beta1IngressTLS
  { extensionsV1beta1IngressTLSHosts :: !(Maybe [Text]) -- ^ "hosts" - Hosts are a list of hosts included in the TLS certificate. The values in this list must match the name/s used in the tlsSecret. Defaults to the wildcard host setting for the loadbalancer controller fulfilling this Ingress, if left unspecified.
  , extensionsV1beta1IngressTLSSecretName :: !(Maybe Text) -- ^ "secretName" - SecretName is the name of the secret used to terminate SSL traffic on 443. Field is left optional to allow SSL routing based on SNI hostname alone. If the SNI host in a listener conflicts with the \&quot;Host\&quot; header field used by an IngressRule, the SNI host is used for termination and value of the Host header is used for routing.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1IngressTLS
instance A.FromJSON ExtensionsV1beta1IngressTLS where
  parseJSON = A.withObject "ExtensionsV1beta1IngressTLS" $ \o ->
    ExtensionsV1beta1IngressTLS
      <$> (o .:? "hosts")
      <*> (o .:? "secretName")

-- | ToJSON ExtensionsV1beta1IngressTLS
instance A.ToJSON ExtensionsV1beta1IngressTLS where
  toJSON ExtensionsV1beta1IngressTLS {..} =
   _omitNulls
      [ "hosts" .= extensionsV1beta1IngressTLSHosts
      , "secretName" .= extensionsV1beta1IngressTLSSecretName
      ]


-- | Construct a value of type 'ExtensionsV1beta1IngressTLS' (by applying it's required fields, if any)
mkExtensionsV1beta1IngressTLS
  :: ExtensionsV1beta1IngressTLS
mkExtensionsV1beta1IngressTLS =
  ExtensionsV1beta1IngressTLS
  { extensionsV1beta1IngressTLSHosts = Nothing
  , extensionsV1beta1IngressTLSSecretName = Nothing
  }

-- ** ExtensionsV1beta1PodSecurityPolicy
-- | ExtensionsV1beta1PodSecurityPolicy
-- PodSecurityPolicy governs the ability to make requests that affect the Security Context that will be applied to a pod and container. Deprecated: use PodSecurityPolicy from policy API Group instead.
data ExtensionsV1beta1PodSecurityPolicy = ExtensionsV1beta1PodSecurityPolicy
  { extensionsV1beta1PodSecurityPolicyApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , extensionsV1beta1PodSecurityPolicyKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , extensionsV1beta1PodSecurityPolicyMetadata :: !(Maybe V1ObjectMeta) -- ^ "metadata"
  , extensionsV1beta1PodSecurityPolicySpec :: !(Maybe ExtensionsV1beta1PodSecurityPolicySpec) -- ^ "spec"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1PodSecurityPolicy
instance A.FromJSON ExtensionsV1beta1PodSecurityPolicy where
  parseJSON = A.withObject "ExtensionsV1beta1PodSecurityPolicy" $ \o ->
    ExtensionsV1beta1PodSecurityPolicy
      <$> (o .:? "apiVersion")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")
      <*> (o .:? "spec")

-- | ToJSON ExtensionsV1beta1PodSecurityPolicy
instance A.ToJSON ExtensionsV1beta1PodSecurityPolicy where
  toJSON ExtensionsV1beta1PodSecurityPolicy {..} =
   _omitNulls
      [ "apiVersion" .= extensionsV1beta1PodSecurityPolicyApiVersion
      , "kind" .= extensionsV1beta1PodSecurityPolicyKind
      , "metadata" .= extensionsV1beta1PodSecurityPolicyMetadata
      , "spec" .= extensionsV1beta1PodSecurityPolicySpec
      ]


-- | Construct a value of type 'ExtensionsV1beta1PodSecurityPolicy' (by applying it's required fields, if any)
mkExtensionsV1beta1PodSecurityPolicy
  :: ExtensionsV1beta1PodSecurityPolicy
mkExtensionsV1beta1PodSecurityPolicy =
  ExtensionsV1beta1PodSecurityPolicy
  { extensionsV1beta1PodSecurityPolicyApiVersion = Nothing
  , extensionsV1beta1PodSecurityPolicyKind = Nothing
  , extensionsV1beta1PodSecurityPolicyMetadata = Nothing
  , extensionsV1beta1PodSecurityPolicySpec = Nothing
  }

-- ** ExtensionsV1beta1PodSecurityPolicyList
-- | ExtensionsV1beta1PodSecurityPolicyList
-- PodSecurityPolicyList is a list of PodSecurityPolicy objects. Deprecated: use PodSecurityPolicyList from policy API Group instead.
data ExtensionsV1beta1PodSecurityPolicyList = ExtensionsV1beta1PodSecurityPolicyList
  { extensionsV1beta1PodSecurityPolicyListApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , extensionsV1beta1PodSecurityPolicyListItems :: !([ExtensionsV1beta1PodSecurityPolicy]) -- ^ /Required/ "items" - items is a list of schema objects.
  , extensionsV1beta1PodSecurityPolicyListKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , extensionsV1beta1PodSecurityPolicyListMetadata :: !(Maybe V1ListMeta) -- ^ "metadata"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1PodSecurityPolicyList
instance A.FromJSON ExtensionsV1beta1PodSecurityPolicyList where
  parseJSON = A.withObject "ExtensionsV1beta1PodSecurityPolicyList" $ \o ->
    ExtensionsV1beta1PodSecurityPolicyList
      <$> (o .:? "apiVersion")
      <*> (o .:  "items")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")

-- | ToJSON ExtensionsV1beta1PodSecurityPolicyList
instance A.ToJSON ExtensionsV1beta1PodSecurityPolicyList where
  toJSON ExtensionsV1beta1PodSecurityPolicyList {..} =
   _omitNulls
      [ "apiVersion" .= extensionsV1beta1PodSecurityPolicyListApiVersion
      , "items" .= extensionsV1beta1PodSecurityPolicyListItems
      , "kind" .= extensionsV1beta1PodSecurityPolicyListKind
      , "metadata" .= extensionsV1beta1PodSecurityPolicyListMetadata
      ]


-- | Construct a value of type 'ExtensionsV1beta1PodSecurityPolicyList' (by applying it's required fields, if any)
mkExtensionsV1beta1PodSecurityPolicyList
  :: [ExtensionsV1beta1PodSecurityPolicy] -- ^ 'extensionsV1beta1PodSecurityPolicyListItems': items is a list of schema objects.
  -> ExtensionsV1beta1PodSecurityPolicyList
mkExtensionsV1beta1PodSecurityPolicyList extensionsV1beta1PodSecurityPolicyListItems =
  ExtensionsV1beta1PodSecurityPolicyList
  { extensionsV1beta1PodSecurityPolicyListApiVersion = Nothing
  , extensionsV1beta1PodSecurityPolicyListItems
  , extensionsV1beta1PodSecurityPolicyListKind = Nothing
  , extensionsV1beta1PodSecurityPolicyListMetadata = Nothing
  }

-- ** ExtensionsV1beta1PodSecurityPolicySpec
-- | ExtensionsV1beta1PodSecurityPolicySpec
-- PodSecurityPolicySpec defines the policy enforced. Deprecated: use PodSecurityPolicySpec from policy API Group instead.
data ExtensionsV1beta1PodSecurityPolicySpec = ExtensionsV1beta1PodSecurityPolicySpec
  { extensionsV1beta1PodSecurityPolicySpecAllowPrivilegeEscalation :: !(Maybe Bool) -- ^ "allowPrivilegeEscalation" - allowPrivilegeEscalation determines if a pod can request to allow privilege escalation. If unspecified, defaults to true.
  , extensionsV1beta1PodSecurityPolicySpecAllowedCsiDrivers :: !(Maybe [ExtensionsV1beta1AllowedCSIDriver]) -- ^ "allowedCSIDrivers" - AllowedCSIDrivers is a whitelist of inline CSI drivers that must be explicitly set to be embedded within a pod spec. An empty value indicates that any CSI driver can be used for inline ephemeral volumes.
  , extensionsV1beta1PodSecurityPolicySpecAllowedCapabilities :: !(Maybe [Text]) -- ^ "allowedCapabilities" - allowedCapabilities is a list of capabilities that can be requested to add to the container. Capabilities in this field may be added at the pod author&#39;s discretion. You must not list a capability in both allowedCapabilities and requiredDropCapabilities.
  , extensionsV1beta1PodSecurityPolicySpecAllowedFlexVolumes :: !(Maybe [ExtensionsV1beta1AllowedFlexVolume]) -- ^ "allowedFlexVolumes" - allowedFlexVolumes is a whitelist of allowed Flexvolumes.  Empty or nil indicates that all Flexvolumes may be used.  This parameter is effective only when the usage of the Flexvolumes is allowed in the \&quot;volumes\&quot; field.
  , extensionsV1beta1PodSecurityPolicySpecAllowedHostPaths :: !(Maybe [ExtensionsV1beta1AllowedHostPath]) -- ^ "allowedHostPaths" - allowedHostPaths is a white list of allowed host paths. Empty indicates that all host paths may be used.
  , extensionsV1beta1PodSecurityPolicySpecAllowedProcMountTypes :: !(Maybe [Text]) -- ^ "allowedProcMountTypes" - AllowedProcMountTypes is a whitelist of allowed ProcMountTypes. Empty or nil indicates that only the DefaultProcMountType may be used. This requires the ProcMountType feature flag to be enabled.
  , extensionsV1beta1PodSecurityPolicySpecAllowedUnsafeSysctls :: !(Maybe [Text]) -- ^ "allowedUnsafeSysctls" - allowedUnsafeSysctls is a list of explicitly allowed unsafe sysctls, defaults to none. Each entry is either a plain sysctl name or ends in \&quot;*\&quot; in which case it is considered as a prefix of allowed sysctls. Single * means all unsafe sysctls are allowed. Kubelet has to whitelist all allowed unsafe sysctls explicitly to avoid rejection.  Examples: e.g. \&quot;foo/*\&quot; allows \&quot;foo/bar\&quot;, \&quot;foo/baz\&quot;, etc. e.g. \&quot;foo.*\&quot; allows \&quot;foo.bar\&quot;, \&quot;foo.baz\&quot;, etc.
  , extensionsV1beta1PodSecurityPolicySpecDefaultAddCapabilities :: !(Maybe [Text]) -- ^ "defaultAddCapabilities" - defaultAddCapabilities is the default set of capabilities that will be added to the container unless the pod spec specifically drops the capability.  You may not list a capability in both defaultAddCapabilities and requiredDropCapabilities. Capabilities added here are implicitly allowed, and need not be included in the allowedCapabilities list.
  , extensionsV1beta1PodSecurityPolicySpecDefaultAllowPrivilegeEscalation :: !(Maybe Bool) -- ^ "defaultAllowPrivilegeEscalation" - defaultAllowPrivilegeEscalation controls the default setting for whether a process can gain more privileges than its parent process.
  , extensionsV1beta1PodSecurityPolicySpecForbiddenSysctls :: !(Maybe [Text]) -- ^ "forbiddenSysctls" - forbiddenSysctls is a list of explicitly forbidden sysctls, defaults to none. Each entry is either a plain sysctl name or ends in \&quot;*\&quot; in which case it is considered as a prefix of forbidden sysctls. Single * means all sysctls are forbidden.  Examples: e.g. \&quot;foo/*\&quot; forbids \&quot;foo/bar\&quot;, \&quot;foo/baz\&quot;, etc. e.g. \&quot;foo.*\&quot; forbids \&quot;foo.bar\&quot;, \&quot;foo.baz\&quot;, etc.
  , extensionsV1beta1PodSecurityPolicySpecFsGroup :: !(ExtensionsV1beta1FSGroupStrategyOptions) -- ^ /Required/ "fsGroup"
  , extensionsV1beta1PodSecurityPolicySpecHostIpc :: !(Maybe Bool) -- ^ "hostIPC" - hostIPC determines if the policy allows the use of HostIPC in the pod spec.
  , extensionsV1beta1PodSecurityPolicySpecHostNetwork :: !(Maybe Bool) -- ^ "hostNetwork" - hostNetwork determines if the policy allows the use of HostNetwork in the pod spec.
  , extensionsV1beta1PodSecurityPolicySpecHostPid :: !(Maybe Bool) -- ^ "hostPID" - hostPID determines if the policy allows the use of HostPID in the pod spec.
  , extensionsV1beta1PodSecurityPolicySpecHostPorts :: !(Maybe [ExtensionsV1beta1HostPortRange]) -- ^ "hostPorts" - hostPorts determines which host port ranges are allowed to be exposed.
  , extensionsV1beta1PodSecurityPolicySpecPrivileged :: !(Maybe Bool) -- ^ "privileged" - privileged determines if a pod can request to be run as privileged.
  , extensionsV1beta1PodSecurityPolicySpecReadOnlyRootFilesystem :: !(Maybe Bool) -- ^ "readOnlyRootFilesystem" - readOnlyRootFilesystem when set to true will force containers to run with a read only root file system.  If the container specifically requests to run with a non-read only root file system the PSP should deny the pod. If set to false the container may run with a read only root file system if it wishes but it will not be forced to.
  , extensionsV1beta1PodSecurityPolicySpecRequiredDropCapabilities :: !(Maybe [Text]) -- ^ "requiredDropCapabilities" - requiredDropCapabilities are the capabilities that will be dropped from the container.  These are required to be dropped and cannot be added.
  , extensionsV1beta1PodSecurityPolicySpecRunAsGroup :: !(Maybe ExtensionsV1beta1RunAsGroupStrategyOptions) -- ^ "runAsGroup"
  , extensionsV1beta1PodSecurityPolicySpecRunAsUser :: !(ExtensionsV1beta1RunAsUserStrategyOptions) -- ^ /Required/ "runAsUser"
  , extensionsV1beta1PodSecurityPolicySpecRuntimeClass :: !(Maybe ExtensionsV1beta1RuntimeClassStrategyOptions) -- ^ "runtimeClass"
  , extensionsV1beta1PodSecurityPolicySpecSeLinux :: !(ExtensionsV1beta1SELinuxStrategyOptions) -- ^ /Required/ "seLinux"
  , extensionsV1beta1PodSecurityPolicySpecSupplementalGroups :: !(ExtensionsV1beta1SupplementalGroupsStrategyOptions) -- ^ /Required/ "supplementalGroups"
  , extensionsV1beta1PodSecurityPolicySpecVolumes :: !(Maybe [Text]) -- ^ "volumes" - volumes is a white list of allowed volume plugins. Empty indicates that no volumes may be used. To allow all volumes you may use &#39;*&#39;.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1PodSecurityPolicySpec
instance A.FromJSON ExtensionsV1beta1PodSecurityPolicySpec where
  parseJSON = A.withObject "ExtensionsV1beta1PodSecurityPolicySpec" $ \o ->
    ExtensionsV1beta1PodSecurityPolicySpec
      <$> (o .:? "allowPrivilegeEscalation")
      <*> (o .:? "allowedCSIDrivers")
      <*> (o .:? "allowedCapabilities")
      <*> (o .:? "allowedFlexVolumes")
      <*> (o .:? "allowedHostPaths")
      <*> (o .:? "allowedProcMountTypes")
      <*> (o .:? "allowedUnsafeSysctls")
      <*> (o .:? "defaultAddCapabilities")
      <*> (o .:? "defaultAllowPrivilegeEscalation")
      <*> (o .:? "forbiddenSysctls")
      <*> (o .:  "fsGroup")
      <*> (o .:? "hostIPC")
      <*> (o .:? "hostNetwork")
      <*> (o .:? "hostPID")
      <*> (o .:? "hostPorts")
      <*> (o .:? "privileged")
      <*> (o .:? "readOnlyRootFilesystem")
      <*> (o .:? "requiredDropCapabilities")
      <*> (o .:? "runAsGroup")
      <*> (o .:  "runAsUser")
      <*> (o .:? "runtimeClass")
      <*> (o .:  "seLinux")
      <*> (o .:  "supplementalGroups")
      <*> (o .:? "volumes")

-- | ToJSON ExtensionsV1beta1PodSecurityPolicySpec
instance A.ToJSON ExtensionsV1beta1PodSecurityPolicySpec where
  toJSON ExtensionsV1beta1PodSecurityPolicySpec {..} =
   _omitNulls
      [ "allowPrivilegeEscalation" .= extensionsV1beta1PodSecurityPolicySpecAllowPrivilegeEscalation
      , "allowedCSIDrivers" .= extensionsV1beta1PodSecurityPolicySpecAllowedCsiDrivers
      , "allowedCapabilities" .= extensionsV1beta1PodSecurityPolicySpecAllowedCapabilities
      , "allowedFlexVolumes" .= extensionsV1beta1PodSecurityPolicySpecAllowedFlexVolumes
      , "allowedHostPaths" .= extensionsV1beta1PodSecurityPolicySpecAllowedHostPaths
      , "allowedProcMountTypes" .= extensionsV1beta1PodSecurityPolicySpecAllowedProcMountTypes
      , "allowedUnsafeSysctls" .= extensionsV1beta1PodSecurityPolicySpecAllowedUnsafeSysctls
      , "defaultAddCapabilities" .= extensionsV1beta1PodSecurityPolicySpecDefaultAddCapabilities
      , "defaultAllowPrivilegeEscalation" .= extensionsV1beta1PodSecurityPolicySpecDefaultAllowPrivilegeEscalation
      , "forbiddenSysctls" .= extensionsV1beta1PodSecurityPolicySpecForbiddenSysctls
      , "fsGroup" .= extensionsV1beta1PodSecurityPolicySpecFsGroup
      , "hostIPC" .= extensionsV1beta1PodSecurityPolicySpecHostIpc
      , "hostNetwork" .= extensionsV1beta1PodSecurityPolicySpecHostNetwork
      , "hostPID" .= extensionsV1beta1PodSecurityPolicySpecHostPid
      , "hostPorts" .= extensionsV1beta1PodSecurityPolicySpecHostPorts
      , "privileged" .= extensionsV1beta1PodSecurityPolicySpecPrivileged
      , "readOnlyRootFilesystem" .= extensionsV1beta1PodSecurityPolicySpecReadOnlyRootFilesystem
      , "requiredDropCapabilities" .= extensionsV1beta1PodSecurityPolicySpecRequiredDropCapabilities
      , "runAsGroup" .= extensionsV1beta1PodSecurityPolicySpecRunAsGroup
      , "runAsUser" .= extensionsV1beta1PodSecurityPolicySpecRunAsUser
      , "runtimeClass" .= extensionsV1beta1PodSecurityPolicySpecRuntimeClass
      , "seLinux" .= extensionsV1beta1PodSecurityPolicySpecSeLinux
      , "supplementalGroups" .= extensionsV1beta1PodSecurityPolicySpecSupplementalGroups
      , "volumes" .= extensionsV1beta1PodSecurityPolicySpecVolumes
      ]


-- | Construct a value of type 'ExtensionsV1beta1PodSecurityPolicySpec' (by applying it's required fields, if any)
mkExtensionsV1beta1PodSecurityPolicySpec
  :: ExtensionsV1beta1FSGroupStrategyOptions -- ^ 'extensionsV1beta1PodSecurityPolicySpecFsGroup' 
  -> ExtensionsV1beta1RunAsUserStrategyOptions -- ^ 'extensionsV1beta1PodSecurityPolicySpecRunAsUser' 
  -> ExtensionsV1beta1SELinuxStrategyOptions -- ^ 'extensionsV1beta1PodSecurityPolicySpecSeLinux' 
  -> ExtensionsV1beta1SupplementalGroupsStrategyOptions -- ^ 'extensionsV1beta1PodSecurityPolicySpecSupplementalGroups' 
  -> ExtensionsV1beta1PodSecurityPolicySpec
mkExtensionsV1beta1PodSecurityPolicySpec extensionsV1beta1PodSecurityPolicySpecFsGroup extensionsV1beta1PodSecurityPolicySpecRunAsUser extensionsV1beta1PodSecurityPolicySpecSeLinux extensionsV1beta1PodSecurityPolicySpecSupplementalGroups =
  ExtensionsV1beta1PodSecurityPolicySpec
  { extensionsV1beta1PodSecurityPolicySpecAllowPrivilegeEscalation = Nothing
  , extensionsV1beta1PodSecurityPolicySpecAllowedCsiDrivers = Nothing
  , extensionsV1beta1PodSecurityPolicySpecAllowedCapabilities = Nothing
  , extensionsV1beta1PodSecurityPolicySpecAllowedFlexVolumes = Nothing
  , extensionsV1beta1PodSecurityPolicySpecAllowedHostPaths = Nothing
  , extensionsV1beta1PodSecurityPolicySpecAllowedProcMountTypes = Nothing
  , extensionsV1beta1PodSecurityPolicySpecAllowedUnsafeSysctls = Nothing
  , extensionsV1beta1PodSecurityPolicySpecDefaultAddCapabilities = Nothing
  , extensionsV1beta1PodSecurityPolicySpecDefaultAllowPrivilegeEscalation = Nothing
  , extensionsV1beta1PodSecurityPolicySpecForbiddenSysctls = Nothing
  , extensionsV1beta1PodSecurityPolicySpecFsGroup
  , extensionsV1beta1PodSecurityPolicySpecHostIpc = Nothing
  , extensionsV1beta1PodSecurityPolicySpecHostNetwork = Nothing
  , extensionsV1beta1PodSecurityPolicySpecHostPid = Nothing
  , extensionsV1beta1PodSecurityPolicySpecHostPorts = Nothing
  , extensionsV1beta1PodSecurityPolicySpecPrivileged = Nothing
  , extensionsV1beta1PodSecurityPolicySpecReadOnlyRootFilesystem = Nothing
  , extensionsV1beta1PodSecurityPolicySpecRequiredDropCapabilities = Nothing
  , extensionsV1beta1PodSecurityPolicySpecRunAsGroup = Nothing
  , extensionsV1beta1PodSecurityPolicySpecRunAsUser
  , extensionsV1beta1PodSecurityPolicySpecRuntimeClass = Nothing
  , extensionsV1beta1PodSecurityPolicySpecSeLinux
  , extensionsV1beta1PodSecurityPolicySpecSupplementalGroups
  , extensionsV1beta1PodSecurityPolicySpecVolumes = Nothing
  }

-- ** ExtensionsV1beta1RollbackConfig
-- | ExtensionsV1beta1RollbackConfig
-- DEPRECATED.
data ExtensionsV1beta1RollbackConfig = ExtensionsV1beta1RollbackConfig
  { extensionsV1beta1RollbackConfigRevision :: !(Maybe Integer) -- ^ "revision" - The revision to rollback to. If set to 0, rollback to the last revision.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1RollbackConfig
instance A.FromJSON ExtensionsV1beta1RollbackConfig where
  parseJSON = A.withObject "ExtensionsV1beta1RollbackConfig" $ \o ->
    ExtensionsV1beta1RollbackConfig
      <$> (o .:? "revision")

-- | ToJSON ExtensionsV1beta1RollbackConfig
instance A.ToJSON ExtensionsV1beta1RollbackConfig where
  toJSON ExtensionsV1beta1RollbackConfig {..} =
   _omitNulls
      [ "revision" .= extensionsV1beta1RollbackConfigRevision
      ]


-- | Construct a value of type 'ExtensionsV1beta1RollbackConfig' (by applying it's required fields, if any)
mkExtensionsV1beta1RollbackConfig
  :: ExtensionsV1beta1RollbackConfig
mkExtensionsV1beta1RollbackConfig =
  ExtensionsV1beta1RollbackConfig
  { extensionsV1beta1RollbackConfigRevision = Nothing
  }

-- ** ExtensionsV1beta1RollingUpdateDeployment
-- | ExtensionsV1beta1RollingUpdateDeployment
-- Spec to control the desired behavior of rolling update.
data ExtensionsV1beta1RollingUpdateDeployment = ExtensionsV1beta1RollingUpdateDeployment
  { extensionsV1beta1RollingUpdateDeploymentMaxSurge :: !(Maybe IntOrString) -- ^ "maxSurge"
  , extensionsV1beta1RollingUpdateDeploymentMaxUnavailable :: !(Maybe IntOrString) -- ^ "maxUnavailable"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1RollingUpdateDeployment
instance A.FromJSON ExtensionsV1beta1RollingUpdateDeployment where
  parseJSON = A.withObject "ExtensionsV1beta1RollingUpdateDeployment" $ \o ->
    ExtensionsV1beta1RollingUpdateDeployment
      <$> (o .:? "maxSurge")
      <*> (o .:? "maxUnavailable")

-- | ToJSON ExtensionsV1beta1RollingUpdateDeployment
instance A.ToJSON ExtensionsV1beta1RollingUpdateDeployment where
  toJSON ExtensionsV1beta1RollingUpdateDeployment {..} =
   _omitNulls
      [ "maxSurge" .= extensionsV1beta1RollingUpdateDeploymentMaxSurge
      , "maxUnavailable" .= extensionsV1beta1RollingUpdateDeploymentMaxUnavailable
      ]


-- | Construct a value of type 'ExtensionsV1beta1RollingUpdateDeployment' (by applying it's required fields, if any)
mkExtensionsV1beta1RollingUpdateDeployment
  :: ExtensionsV1beta1RollingUpdateDeployment
mkExtensionsV1beta1RollingUpdateDeployment =
  ExtensionsV1beta1RollingUpdateDeployment
  { extensionsV1beta1RollingUpdateDeploymentMaxSurge = Nothing
  , extensionsV1beta1RollingUpdateDeploymentMaxUnavailable = Nothing
  }

-- ** ExtensionsV1beta1RunAsGroupStrategyOptions
-- | ExtensionsV1beta1RunAsGroupStrategyOptions
-- RunAsGroupStrategyOptions defines the strategy type and any options used to create the strategy. Deprecated: use RunAsGroupStrategyOptions from policy API Group instead.
data ExtensionsV1beta1RunAsGroupStrategyOptions = ExtensionsV1beta1RunAsGroupStrategyOptions
  { extensionsV1beta1RunAsGroupStrategyOptionsRanges :: !(Maybe [ExtensionsV1beta1IDRange]) -- ^ "ranges" - ranges are the allowed ranges of gids that may be used. If you would like to force a single gid then supply a single range with the same start and end. Required for MustRunAs.
  , extensionsV1beta1RunAsGroupStrategyOptionsRule :: !(Text) -- ^ /Required/ "rule" - rule is the strategy that will dictate the allowable RunAsGroup values that may be set.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1RunAsGroupStrategyOptions
instance A.FromJSON ExtensionsV1beta1RunAsGroupStrategyOptions where
  parseJSON = A.withObject "ExtensionsV1beta1RunAsGroupStrategyOptions" $ \o ->
    ExtensionsV1beta1RunAsGroupStrategyOptions
      <$> (o .:? "ranges")
      <*> (o .:  "rule")

-- | ToJSON ExtensionsV1beta1RunAsGroupStrategyOptions
instance A.ToJSON ExtensionsV1beta1RunAsGroupStrategyOptions where
  toJSON ExtensionsV1beta1RunAsGroupStrategyOptions {..} =
   _omitNulls
      [ "ranges" .= extensionsV1beta1RunAsGroupStrategyOptionsRanges
      , "rule" .= extensionsV1beta1RunAsGroupStrategyOptionsRule
      ]


-- | Construct a value of type 'ExtensionsV1beta1RunAsGroupStrategyOptions' (by applying it's required fields, if any)
mkExtensionsV1beta1RunAsGroupStrategyOptions
  :: Text -- ^ 'extensionsV1beta1RunAsGroupStrategyOptionsRule': rule is the strategy that will dictate the allowable RunAsGroup values that may be set.
  -> ExtensionsV1beta1RunAsGroupStrategyOptions
mkExtensionsV1beta1RunAsGroupStrategyOptions extensionsV1beta1RunAsGroupStrategyOptionsRule =
  ExtensionsV1beta1RunAsGroupStrategyOptions
  { extensionsV1beta1RunAsGroupStrategyOptionsRanges = Nothing
  , extensionsV1beta1RunAsGroupStrategyOptionsRule
  }

-- ** ExtensionsV1beta1RunAsUserStrategyOptions
-- | ExtensionsV1beta1RunAsUserStrategyOptions
-- RunAsUserStrategyOptions defines the strategy type and any options used to create the strategy. Deprecated: use RunAsUserStrategyOptions from policy API Group instead.
data ExtensionsV1beta1RunAsUserStrategyOptions = ExtensionsV1beta1RunAsUserStrategyOptions
  { extensionsV1beta1RunAsUserStrategyOptionsRanges :: !(Maybe [ExtensionsV1beta1IDRange]) -- ^ "ranges" - ranges are the allowed ranges of uids that may be used. If you would like to force a single uid then supply a single range with the same start and end. Required for MustRunAs.
  , extensionsV1beta1RunAsUserStrategyOptionsRule :: !(Text) -- ^ /Required/ "rule" - rule is the strategy that will dictate the allowable RunAsUser values that may be set.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1RunAsUserStrategyOptions
instance A.FromJSON ExtensionsV1beta1RunAsUserStrategyOptions where
  parseJSON = A.withObject "ExtensionsV1beta1RunAsUserStrategyOptions" $ \o ->
    ExtensionsV1beta1RunAsUserStrategyOptions
      <$> (o .:? "ranges")
      <*> (o .:  "rule")

-- | ToJSON ExtensionsV1beta1RunAsUserStrategyOptions
instance A.ToJSON ExtensionsV1beta1RunAsUserStrategyOptions where
  toJSON ExtensionsV1beta1RunAsUserStrategyOptions {..} =
   _omitNulls
      [ "ranges" .= extensionsV1beta1RunAsUserStrategyOptionsRanges
      , "rule" .= extensionsV1beta1RunAsUserStrategyOptionsRule
      ]


-- | Construct a value of type 'ExtensionsV1beta1RunAsUserStrategyOptions' (by applying it's required fields, if any)
mkExtensionsV1beta1RunAsUserStrategyOptions
  :: Text -- ^ 'extensionsV1beta1RunAsUserStrategyOptionsRule': rule is the strategy that will dictate the allowable RunAsUser values that may be set.
  -> ExtensionsV1beta1RunAsUserStrategyOptions
mkExtensionsV1beta1RunAsUserStrategyOptions extensionsV1beta1RunAsUserStrategyOptionsRule =
  ExtensionsV1beta1RunAsUserStrategyOptions
  { extensionsV1beta1RunAsUserStrategyOptionsRanges = Nothing
  , extensionsV1beta1RunAsUserStrategyOptionsRule
  }

-- ** ExtensionsV1beta1RuntimeClassStrategyOptions
-- | ExtensionsV1beta1RuntimeClassStrategyOptions
-- RuntimeClassStrategyOptions define the strategy that will dictate the allowable RuntimeClasses for a pod.
data ExtensionsV1beta1RuntimeClassStrategyOptions = ExtensionsV1beta1RuntimeClassStrategyOptions
  { extensionsV1beta1RuntimeClassStrategyOptionsAllowedRuntimeClassNames :: !([Text]) -- ^ /Required/ "allowedRuntimeClassNames" - allowedRuntimeClassNames is a whitelist of RuntimeClass names that may be specified on a pod. A value of \&quot;*\&quot; means that any RuntimeClass name is allowed, and must be the only item in the list. An empty list requires the RuntimeClassName field to be unset.
  , extensionsV1beta1RuntimeClassStrategyOptionsDefaultRuntimeClassName :: !(Maybe Text) -- ^ "defaultRuntimeClassName" - defaultRuntimeClassName is the default RuntimeClassName to set on the pod. The default MUST be allowed by the allowedRuntimeClassNames list. A value of nil does not mutate the Pod.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1RuntimeClassStrategyOptions
instance A.FromJSON ExtensionsV1beta1RuntimeClassStrategyOptions where
  parseJSON = A.withObject "ExtensionsV1beta1RuntimeClassStrategyOptions" $ \o ->
    ExtensionsV1beta1RuntimeClassStrategyOptions
      <$> (o .:  "allowedRuntimeClassNames")
      <*> (o .:? "defaultRuntimeClassName")

-- | ToJSON ExtensionsV1beta1RuntimeClassStrategyOptions
instance A.ToJSON ExtensionsV1beta1RuntimeClassStrategyOptions where
  toJSON ExtensionsV1beta1RuntimeClassStrategyOptions {..} =
   _omitNulls
      [ "allowedRuntimeClassNames" .= extensionsV1beta1RuntimeClassStrategyOptionsAllowedRuntimeClassNames
      , "defaultRuntimeClassName" .= extensionsV1beta1RuntimeClassStrategyOptionsDefaultRuntimeClassName
      ]


-- | Construct a value of type 'ExtensionsV1beta1RuntimeClassStrategyOptions' (by applying it's required fields, if any)
mkExtensionsV1beta1RuntimeClassStrategyOptions
  :: [Text] -- ^ 'extensionsV1beta1RuntimeClassStrategyOptionsAllowedRuntimeClassNames': allowedRuntimeClassNames is a whitelist of RuntimeClass names that may be specified on a pod. A value of \"*\" means that any RuntimeClass name is allowed, and must be the only item in the list. An empty list requires the RuntimeClassName field to be unset.
  -> ExtensionsV1beta1RuntimeClassStrategyOptions
mkExtensionsV1beta1RuntimeClassStrategyOptions extensionsV1beta1RuntimeClassStrategyOptionsAllowedRuntimeClassNames =
  ExtensionsV1beta1RuntimeClassStrategyOptions
  { extensionsV1beta1RuntimeClassStrategyOptionsAllowedRuntimeClassNames
  , extensionsV1beta1RuntimeClassStrategyOptionsDefaultRuntimeClassName = Nothing
  }

-- ** ExtensionsV1beta1SELinuxStrategyOptions
-- | ExtensionsV1beta1SELinuxStrategyOptions
-- SELinuxStrategyOptions defines the strategy type and any options used to create the strategy. Deprecated: use SELinuxStrategyOptions from policy API Group instead.
data ExtensionsV1beta1SELinuxStrategyOptions = ExtensionsV1beta1SELinuxStrategyOptions
  { extensionsV1beta1SELinuxStrategyOptionsRule :: !(Text) -- ^ /Required/ "rule" - rule is the strategy that will dictate the allowable labels that may be set.
  , extensionsV1beta1SELinuxStrategyOptionsSeLinuxOptions :: !(Maybe V1SELinuxOptions) -- ^ "seLinuxOptions"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1SELinuxStrategyOptions
instance A.FromJSON ExtensionsV1beta1SELinuxStrategyOptions where
  parseJSON = A.withObject "ExtensionsV1beta1SELinuxStrategyOptions" $ \o ->
    ExtensionsV1beta1SELinuxStrategyOptions
      <$> (o .:  "rule")
      <*> (o .:? "seLinuxOptions")

-- | ToJSON ExtensionsV1beta1SELinuxStrategyOptions
instance A.ToJSON ExtensionsV1beta1SELinuxStrategyOptions where
  toJSON ExtensionsV1beta1SELinuxStrategyOptions {..} =
   _omitNulls
      [ "rule" .= extensionsV1beta1SELinuxStrategyOptionsRule
      , "seLinuxOptions" .= extensionsV1beta1SELinuxStrategyOptionsSeLinuxOptions
      ]


-- | Construct a value of type 'ExtensionsV1beta1SELinuxStrategyOptions' (by applying it's required fields, if any)
mkExtensionsV1beta1SELinuxStrategyOptions
  :: Text -- ^ 'extensionsV1beta1SELinuxStrategyOptionsRule': rule is the strategy that will dictate the allowable labels that may be set.
  -> ExtensionsV1beta1SELinuxStrategyOptions
mkExtensionsV1beta1SELinuxStrategyOptions extensionsV1beta1SELinuxStrategyOptionsRule =
  ExtensionsV1beta1SELinuxStrategyOptions
  { extensionsV1beta1SELinuxStrategyOptionsRule
  , extensionsV1beta1SELinuxStrategyOptionsSeLinuxOptions = Nothing
  }

-- ** ExtensionsV1beta1Scale
-- | ExtensionsV1beta1Scale
-- represents a scaling request for a resource.
data ExtensionsV1beta1Scale = ExtensionsV1beta1Scale
  { extensionsV1beta1ScaleApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , extensionsV1beta1ScaleKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , extensionsV1beta1ScaleMetadata :: !(Maybe V1ObjectMeta) -- ^ "metadata"
  , extensionsV1beta1ScaleSpec :: !(Maybe ExtensionsV1beta1ScaleSpec) -- ^ "spec"
  , extensionsV1beta1ScaleStatus :: !(Maybe ExtensionsV1beta1ScaleStatus) -- ^ "status"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1Scale
instance A.FromJSON ExtensionsV1beta1Scale where
  parseJSON = A.withObject "ExtensionsV1beta1Scale" $ \o ->
    ExtensionsV1beta1Scale
      <$> (o .:? "apiVersion")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")
      <*> (o .:? "spec")
      <*> (o .:? "status")

-- | ToJSON ExtensionsV1beta1Scale
instance A.ToJSON ExtensionsV1beta1Scale where
  toJSON ExtensionsV1beta1Scale {..} =
   _omitNulls
      [ "apiVersion" .= extensionsV1beta1ScaleApiVersion
      , "kind" .= extensionsV1beta1ScaleKind
      , "metadata" .= extensionsV1beta1ScaleMetadata
      , "spec" .= extensionsV1beta1ScaleSpec
      , "status" .= extensionsV1beta1ScaleStatus
      ]


-- | Construct a value of type 'ExtensionsV1beta1Scale' (by applying it's required fields, if any)
mkExtensionsV1beta1Scale
  :: ExtensionsV1beta1Scale
mkExtensionsV1beta1Scale =
  ExtensionsV1beta1Scale
  { extensionsV1beta1ScaleApiVersion = Nothing
  , extensionsV1beta1ScaleKind = Nothing
  , extensionsV1beta1ScaleMetadata = Nothing
  , extensionsV1beta1ScaleSpec = Nothing
  , extensionsV1beta1ScaleStatus = Nothing
  }

-- ** ExtensionsV1beta1ScaleSpec
-- | ExtensionsV1beta1ScaleSpec
-- describes the attributes of a scale subresource
data ExtensionsV1beta1ScaleSpec = ExtensionsV1beta1ScaleSpec
  { extensionsV1beta1ScaleSpecReplicas :: !(Maybe Int) -- ^ "replicas" - desired number of instances for the scaled object.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1ScaleSpec
instance A.FromJSON ExtensionsV1beta1ScaleSpec where
  parseJSON = A.withObject "ExtensionsV1beta1ScaleSpec" $ \o ->
    ExtensionsV1beta1ScaleSpec
      <$> (o .:? "replicas")

-- | ToJSON ExtensionsV1beta1ScaleSpec
instance A.ToJSON ExtensionsV1beta1ScaleSpec where
  toJSON ExtensionsV1beta1ScaleSpec {..} =
   _omitNulls
      [ "replicas" .= extensionsV1beta1ScaleSpecReplicas
      ]


-- | Construct a value of type 'ExtensionsV1beta1ScaleSpec' (by applying it's required fields, if any)
mkExtensionsV1beta1ScaleSpec
  :: ExtensionsV1beta1ScaleSpec
mkExtensionsV1beta1ScaleSpec =
  ExtensionsV1beta1ScaleSpec
  { extensionsV1beta1ScaleSpecReplicas = Nothing
  }

-- ** ExtensionsV1beta1ScaleStatus
-- | ExtensionsV1beta1ScaleStatus
-- represents the current status of a scale subresource.
data ExtensionsV1beta1ScaleStatus = ExtensionsV1beta1ScaleStatus
  { extensionsV1beta1ScaleStatusReplicas :: !(Int) -- ^ /Required/ "replicas" - actual number of observed instances of the scaled object.
  , extensionsV1beta1ScaleStatusSelector :: !(Maybe (Map.Map String Text)) -- ^ "selector" - label query over pods that should match the replicas count. More info: http://kubernetes.io/docs/user-guide/labels#label-selectors
  , extensionsV1beta1ScaleStatusTargetSelector :: !(Maybe Text) -- ^ "targetSelector" - label selector for pods that should match the replicas count. This is a serializated version of both map-based and more expressive set-based selectors. This is done to avoid introspection in the clients. The string will be in the same format as the query-param syntax. If the target type only supports map-based selectors, both this field and map-based selector field are populated. More info: https://kubernetes.io/docs/concepts/overview/working-with-objects/labels/#label-selectors
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1ScaleStatus
instance A.FromJSON ExtensionsV1beta1ScaleStatus where
  parseJSON = A.withObject "ExtensionsV1beta1ScaleStatus" $ \o ->
    ExtensionsV1beta1ScaleStatus
      <$> (o .:  "replicas")
      <*> (o .:? "selector")
      <*> (o .:? "targetSelector")

-- | ToJSON ExtensionsV1beta1ScaleStatus
instance A.ToJSON ExtensionsV1beta1ScaleStatus where
  toJSON ExtensionsV1beta1ScaleStatus {..} =
   _omitNulls
      [ "replicas" .= extensionsV1beta1ScaleStatusReplicas
      , "selector" .= extensionsV1beta1ScaleStatusSelector
      , "targetSelector" .= extensionsV1beta1ScaleStatusTargetSelector
      ]


-- | Construct a value of type 'ExtensionsV1beta1ScaleStatus' (by applying it's required fields, if any)
mkExtensionsV1beta1ScaleStatus
  :: Int -- ^ 'extensionsV1beta1ScaleStatusReplicas': actual number of observed instances of the scaled object.
  -> ExtensionsV1beta1ScaleStatus
mkExtensionsV1beta1ScaleStatus extensionsV1beta1ScaleStatusReplicas =
  ExtensionsV1beta1ScaleStatus
  { extensionsV1beta1ScaleStatusReplicas
  , extensionsV1beta1ScaleStatusSelector = Nothing
  , extensionsV1beta1ScaleStatusTargetSelector = Nothing
  }

-- ** ExtensionsV1beta1SupplementalGroupsStrategyOptions
-- | ExtensionsV1beta1SupplementalGroupsStrategyOptions
-- SupplementalGroupsStrategyOptions defines the strategy type and options used to create the strategy. Deprecated: use SupplementalGroupsStrategyOptions from policy API Group instead.
data ExtensionsV1beta1SupplementalGroupsStrategyOptions = ExtensionsV1beta1SupplementalGroupsStrategyOptions
  { extensionsV1beta1SupplementalGroupsStrategyOptionsRanges :: !(Maybe [ExtensionsV1beta1IDRange]) -- ^ "ranges" - ranges are the allowed ranges of supplemental groups.  If you would like to force a single supplemental group then supply a single range with the same start and end. Required for MustRunAs.
  , extensionsV1beta1SupplementalGroupsStrategyOptionsRule :: !(Maybe Text) -- ^ "rule" - rule is the strategy that will dictate what supplemental groups is used in the SecurityContext.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON ExtensionsV1beta1SupplementalGroupsStrategyOptions
instance A.FromJSON ExtensionsV1beta1SupplementalGroupsStrategyOptions where
  parseJSON = A.withObject "ExtensionsV1beta1SupplementalGroupsStrategyOptions" $ \o ->
    ExtensionsV1beta1SupplementalGroupsStrategyOptions
      <$> (o .:? "ranges")
      <*> (o .:? "rule")

-- | ToJSON ExtensionsV1beta1SupplementalGroupsStrategyOptions
instance A.ToJSON ExtensionsV1beta1SupplementalGroupsStrategyOptions where
  toJSON ExtensionsV1beta1SupplementalGroupsStrategyOptions {..} =
   _omitNulls
      [ "ranges" .= extensionsV1beta1SupplementalGroupsStrategyOptionsRanges
      , "rule" .= extensionsV1beta1SupplementalGroupsStrategyOptionsRule
      ]


-- | Construct a value of type 'ExtensionsV1beta1SupplementalGroupsStrategyOptions' (by applying it's required fields, if any)
mkExtensionsV1beta1SupplementalGroupsStrategyOptions
  :: ExtensionsV1beta1SupplementalGroupsStrategyOptions
mkExtensionsV1beta1SupplementalGroupsStrategyOptions =
  ExtensionsV1beta1SupplementalGroupsStrategyOptions
  { extensionsV1beta1SupplementalGroupsStrategyOptionsRanges = Nothing
  , extensionsV1beta1SupplementalGroupsStrategyOptionsRule = Nothing
  }

-- ** NetworkingV1beta1HTTPIngressPath
-- | NetworkingV1beta1HTTPIngressPath
-- HTTPIngressPath associates a path regex with a backend. Incoming urls matching the path are forwarded to the backend.
data NetworkingV1beta1HTTPIngressPath = NetworkingV1beta1HTTPIngressPath
  { networkingV1beta1HTTPIngressPathBackend :: !(NetworkingV1beta1IngressBackend) -- ^ /Required/ "backend"
  , networkingV1beta1HTTPIngressPathPath :: !(Maybe Text) -- ^ "path" - Path is an extended POSIX regex as defined by IEEE Std 1003.1, (i.e this follows the egrep/unix syntax, not the perl syntax) matched against the path of an incoming request. Currently it can contain characters disallowed from the conventional \&quot;path\&quot; part of a URL as defined by RFC 3986. Paths must begin with a &#39;/&#39;. If unspecified, the path defaults to a catch all sending traffic to the backend.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON NetworkingV1beta1HTTPIngressPath
instance A.FromJSON NetworkingV1beta1HTTPIngressPath where
  parseJSON = A.withObject "NetworkingV1beta1HTTPIngressPath" $ \o ->
    NetworkingV1beta1HTTPIngressPath
      <$> (o .:  "backend")
      <*> (o .:? "path")

-- | ToJSON NetworkingV1beta1HTTPIngressPath
instance A.ToJSON NetworkingV1beta1HTTPIngressPath where
  toJSON NetworkingV1beta1HTTPIngressPath {..} =
   _omitNulls
      [ "backend" .= networkingV1beta1HTTPIngressPathBackend
      , "path" .= networkingV1beta1HTTPIngressPathPath
      ]


-- | Construct a value of type 'NetworkingV1beta1HTTPIngressPath' (by applying it's required fields, if any)
mkNetworkingV1beta1HTTPIngressPath
  :: NetworkingV1beta1IngressBackend -- ^ 'networkingV1beta1HTTPIngressPathBackend' 
  -> NetworkingV1beta1HTTPIngressPath
mkNetworkingV1beta1HTTPIngressPath networkingV1beta1HTTPIngressPathBackend =
  NetworkingV1beta1HTTPIngressPath
  { networkingV1beta1HTTPIngressPathBackend
  , networkingV1beta1HTTPIngressPathPath = Nothing
  }

-- ** NetworkingV1beta1HTTPIngressRuleValue
-- | NetworkingV1beta1HTTPIngressRuleValue
-- HTTPIngressRuleValue is a list of http selectors pointing to backends. In the example: http://<host>/<path>?<searchpart> -> backend where where parts of the url correspond to RFC 3986, this resource will be used to match against everything after the last '/' and before the first '?' or '#'.
data NetworkingV1beta1HTTPIngressRuleValue = NetworkingV1beta1HTTPIngressRuleValue
  { networkingV1beta1HTTPIngressRuleValuePaths :: !([NetworkingV1beta1HTTPIngressPath]) -- ^ /Required/ "paths" - A collection of paths that map requests to backends.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON NetworkingV1beta1HTTPIngressRuleValue
instance A.FromJSON NetworkingV1beta1HTTPIngressRuleValue where
  parseJSON = A.withObject "NetworkingV1beta1HTTPIngressRuleValue" $ \o ->
    NetworkingV1beta1HTTPIngressRuleValue
      <$> (o .:  "paths")

-- | ToJSON NetworkingV1beta1HTTPIngressRuleValue
instance A.ToJSON NetworkingV1beta1HTTPIngressRuleValue where
  toJSON NetworkingV1beta1HTTPIngressRuleValue {..} =
   _omitNulls
      [ "paths" .= networkingV1beta1HTTPIngressRuleValuePaths
      ]


-- | Construct a value of type 'NetworkingV1beta1HTTPIngressRuleValue' (by applying it's required fields, if any)
mkNetworkingV1beta1HTTPIngressRuleValue
  :: [NetworkingV1beta1HTTPIngressPath] -- ^ 'networkingV1beta1HTTPIngressRuleValuePaths': A collection of paths that map requests to backends.
  -> NetworkingV1beta1HTTPIngressRuleValue
mkNetworkingV1beta1HTTPIngressRuleValue networkingV1beta1HTTPIngressRuleValuePaths =
  NetworkingV1beta1HTTPIngressRuleValue
  { networkingV1beta1HTTPIngressRuleValuePaths
  }

-- ** NetworkingV1beta1Ingress
-- | NetworkingV1beta1Ingress
-- Ingress is a collection of rules that allow inbound connections to reach the endpoints defined by a backend. An Ingress can be configured to give services externally-reachable urls, load balance traffic, terminate SSL, offer name based virtual hosting etc.
data NetworkingV1beta1Ingress = NetworkingV1beta1Ingress
  { networkingV1beta1IngressApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , networkingV1beta1IngressKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , networkingV1beta1IngressMetadata :: !(Maybe V1ObjectMeta) -- ^ "metadata"
  , networkingV1beta1IngressSpec :: !(Maybe NetworkingV1beta1IngressSpec) -- ^ "spec"
  , networkingV1beta1IngressStatus :: !(Maybe NetworkingV1beta1IngressStatus) -- ^ "status"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON NetworkingV1beta1Ingress
instance A.FromJSON NetworkingV1beta1Ingress where
  parseJSON = A.withObject "NetworkingV1beta1Ingress" $ \o ->
    NetworkingV1beta1Ingress
      <$> (o .:? "apiVersion")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")
      <*> (o .:? "spec")
      <*> (o .:? "status")

-- | ToJSON NetworkingV1beta1Ingress
instance A.ToJSON NetworkingV1beta1Ingress where
  toJSON NetworkingV1beta1Ingress {..} =
   _omitNulls
      [ "apiVersion" .= networkingV1beta1IngressApiVersion
      , "kind" .= networkingV1beta1IngressKind
      , "metadata" .= networkingV1beta1IngressMetadata
      , "spec" .= networkingV1beta1IngressSpec
      , "status" .= networkingV1beta1IngressStatus
      ]


-- | Construct a value of type 'NetworkingV1beta1Ingress' (by applying it's required fields, if any)
mkNetworkingV1beta1Ingress
  :: NetworkingV1beta1Ingress
mkNetworkingV1beta1Ingress =
  NetworkingV1beta1Ingress
  { networkingV1beta1IngressApiVersion = Nothing
  , networkingV1beta1IngressKind = Nothing
  , networkingV1beta1IngressMetadata = Nothing
  , networkingV1beta1IngressSpec = Nothing
  , networkingV1beta1IngressStatus = Nothing
  }

-- ** NetworkingV1beta1IngressBackend
-- | NetworkingV1beta1IngressBackend
-- IngressBackend describes all endpoints for a given service and port.
data NetworkingV1beta1IngressBackend = NetworkingV1beta1IngressBackend
  { networkingV1beta1IngressBackendServiceName :: !(Text) -- ^ /Required/ "serviceName" - Specifies the name of the referenced service.
  , networkingV1beta1IngressBackendServicePort :: !(IntOrString) -- ^ /Required/ "servicePort"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON NetworkingV1beta1IngressBackend
instance A.FromJSON NetworkingV1beta1IngressBackend where
  parseJSON = A.withObject "NetworkingV1beta1IngressBackend" $ \o ->
    NetworkingV1beta1IngressBackend
      <$> (o .:  "serviceName")
      <*> (o .:  "servicePort")

-- | ToJSON NetworkingV1beta1IngressBackend
instance A.ToJSON NetworkingV1beta1IngressBackend where
  toJSON NetworkingV1beta1IngressBackend {..} =
   _omitNulls
      [ "serviceName" .= networkingV1beta1IngressBackendServiceName
      , "servicePort" .= networkingV1beta1IngressBackendServicePort
      ]


-- | Construct a value of type 'NetworkingV1beta1IngressBackend' (by applying it's required fields, if any)
mkNetworkingV1beta1IngressBackend
  :: Text -- ^ 'networkingV1beta1IngressBackendServiceName': Specifies the name of the referenced service.
  -> IntOrString -- ^ 'networkingV1beta1IngressBackendServicePort' 
  -> NetworkingV1beta1IngressBackend
mkNetworkingV1beta1IngressBackend networkingV1beta1IngressBackendServiceName networkingV1beta1IngressBackendServicePort =
  NetworkingV1beta1IngressBackend
  { networkingV1beta1IngressBackendServiceName
  , networkingV1beta1IngressBackendServicePort
  }

-- ** NetworkingV1beta1IngressList
-- | NetworkingV1beta1IngressList
-- IngressList is a collection of Ingress.
data NetworkingV1beta1IngressList = NetworkingV1beta1IngressList
  { networkingV1beta1IngressListApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , networkingV1beta1IngressListItems :: !([NetworkingV1beta1Ingress]) -- ^ /Required/ "items" - Items is the list of Ingress.
  , networkingV1beta1IngressListKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , networkingV1beta1IngressListMetadata :: !(Maybe V1ListMeta) -- ^ "metadata"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON NetworkingV1beta1IngressList
instance A.FromJSON NetworkingV1beta1IngressList where
  parseJSON = A.withObject "NetworkingV1beta1IngressList" $ \o ->
    NetworkingV1beta1IngressList
      <$> (o .:? "apiVersion")
      <*> (o .:  "items")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")

-- | ToJSON NetworkingV1beta1IngressList
instance A.ToJSON NetworkingV1beta1IngressList where
  toJSON NetworkingV1beta1IngressList {..} =
   _omitNulls
      [ "apiVersion" .= networkingV1beta1IngressListApiVersion
      , "items" .= networkingV1beta1IngressListItems
      , "kind" .= networkingV1beta1IngressListKind
      , "metadata" .= networkingV1beta1IngressListMetadata
      ]


-- | Construct a value of type 'NetworkingV1beta1IngressList' (by applying it's required fields, if any)
mkNetworkingV1beta1IngressList
  :: [NetworkingV1beta1Ingress] -- ^ 'networkingV1beta1IngressListItems': Items is the list of Ingress.
  -> NetworkingV1beta1IngressList
mkNetworkingV1beta1IngressList networkingV1beta1IngressListItems =
  NetworkingV1beta1IngressList
  { networkingV1beta1IngressListApiVersion = Nothing
  , networkingV1beta1IngressListItems
  , networkingV1beta1IngressListKind = Nothing
  , networkingV1beta1IngressListMetadata = Nothing
  }

-- ** NetworkingV1beta1IngressRule
-- | NetworkingV1beta1IngressRule
-- IngressRule represents the rules mapping the paths under a specified host to the related backend services. Incoming requests are first evaluated for a host match, then routed to the backend associated with the matching IngressRuleValue.
data NetworkingV1beta1IngressRule = NetworkingV1beta1IngressRule
  { networkingV1beta1IngressRuleHost :: !(Maybe Text) -- ^ "host" - Host is the fully qualified domain name of a network host, as defined by RFC 3986. Note the following deviations from the \&quot;host\&quot; part of the URI as defined in the RFC: 1. IPs are not allowed. Currently an IngressRuleValue can only apply to the    IP in the Spec of the parent Ingress. 2. The &#x60;:&#x60; delimiter is not respected because ports are not allowed.    Currently the port of an Ingress is implicitly :80 for http and    :443 for https. Both these may change in the future. Incoming requests are matched against the host before the IngressRuleValue. If the host is unspecified, the Ingress routes all traffic based on the specified IngressRuleValue.
  , networkingV1beta1IngressRuleHttp :: !(Maybe NetworkingV1beta1HTTPIngressRuleValue) -- ^ "http"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON NetworkingV1beta1IngressRule
instance A.FromJSON NetworkingV1beta1IngressRule where
  parseJSON = A.withObject "NetworkingV1beta1IngressRule" $ \o ->
    NetworkingV1beta1IngressRule
      <$> (o .:? "host")
      <*> (o .:? "http")

-- | ToJSON NetworkingV1beta1IngressRule
instance A.ToJSON NetworkingV1beta1IngressRule where
  toJSON NetworkingV1beta1IngressRule {..} =
   _omitNulls
      [ "host" .= networkingV1beta1IngressRuleHost
      , "http" .= networkingV1beta1IngressRuleHttp
      ]


-- | Construct a value of type 'NetworkingV1beta1IngressRule' (by applying it's required fields, if any)
mkNetworkingV1beta1IngressRule
  :: NetworkingV1beta1IngressRule
mkNetworkingV1beta1IngressRule =
  NetworkingV1beta1IngressRule
  { networkingV1beta1IngressRuleHost = Nothing
  , networkingV1beta1IngressRuleHttp = Nothing
  }

-- ** NetworkingV1beta1IngressSpec
-- | NetworkingV1beta1IngressSpec
-- IngressSpec describes the Ingress the user wishes to exist.
data NetworkingV1beta1IngressSpec = NetworkingV1beta1IngressSpec
  { networkingV1beta1IngressSpecBackend :: !(Maybe NetworkingV1beta1IngressBackend) -- ^ "backend"
  , networkingV1beta1IngressSpecRules :: !(Maybe [NetworkingV1beta1IngressRule]) -- ^ "rules" - A list of host rules used to configure the Ingress. If unspecified, or no rule matches, all traffic is sent to the default backend.
  , networkingV1beta1IngressSpecTls :: !(Maybe [NetworkingV1beta1IngressTLS]) -- ^ "tls" - TLS configuration. Currently the Ingress only supports a single TLS port, 443. If multiple members of this list specify different hosts, they will be multiplexed on the same port according to the hostname specified through the SNI TLS extension, if the ingress controller fulfilling the ingress supports SNI.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON NetworkingV1beta1IngressSpec
instance A.FromJSON NetworkingV1beta1IngressSpec where
  parseJSON = A.withObject "NetworkingV1beta1IngressSpec" $ \o ->
    NetworkingV1beta1IngressSpec
      <$> (o .:? "backend")
      <*> (o .:? "rules")
      <*> (o .:? "tls")

-- | ToJSON NetworkingV1beta1IngressSpec
instance A.ToJSON NetworkingV1beta1IngressSpec where
  toJSON NetworkingV1beta1IngressSpec {..} =
   _omitNulls
      [ "backend" .= networkingV1beta1IngressSpecBackend
      , "rules" .= networkingV1beta1IngressSpecRules
      , "tls" .= networkingV1beta1IngressSpecTls
      ]


-- | Construct a value of type 'NetworkingV1beta1IngressSpec' (by applying it's required fields, if any)
mkNetworkingV1beta1IngressSpec
  :: NetworkingV1beta1IngressSpec
mkNetworkingV1beta1IngressSpec =
  NetworkingV1beta1IngressSpec
  { networkingV1beta1IngressSpecBackend = Nothing
  , networkingV1beta1IngressSpecRules = Nothing
  , networkingV1beta1IngressSpecTls = Nothing
  }

-- ** NetworkingV1beta1IngressStatus
-- | NetworkingV1beta1IngressStatus
-- IngressStatus describe the current state of the Ingress.
data NetworkingV1beta1IngressStatus = NetworkingV1beta1IngressStatus
  { networkingV1beta1IngressStatusLoadBalancer :: !(Maybe V1LoadBalancerStatus) -- ^ "loadBalancer"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON NetworkingV1beta1IngressStatus
instance A.FromJSON NetworkingV1beta1IngressStatus where
  parseJSON = A.withObject "NetworkingV1beta1IngressStatus" $ \o ->
    NetworkingV1beta1IngressStatus
      <$> (o .:? "loadBalancer")

-- | ToJSON NetworkingV1beta1IngressStatus
instance A.ToJSON NetworkingV1beta1IngressStatus where
  toJSON NetworkingV1beta1IngressStatus {..} =
   _omitNulls
      [ "loadBalancer" .= networkingV1beta1IngressStatusLoadBalancer
      ]


-- | Construct a value of type 'NetworkingV1beta1IngressStatus' (by applying it's required fields, if any)
mkNetworkingV1beta1IngressStatus
  :: NetworkingV1beta1IngressStatus
mkNetworkingV1beta1IngressStatus =
  NetworkingV1beta1IngressStatus
  { networkingV1beta1IngressStatusLoadBalancer = Nothing
  }

-- ** NetworkingV1beta1IngressTLS
-- | NetworkingV1beta1IngressTLS
-- IngressTLS describes the transport layer security associated with an Ingress.
data NetworkingV1beta1IngressTLS = NetworkingV1beta1IngressTLS
  { networkingV1beta1IngressTLSHosts :: !(Maybe [Text]) -- ^ "hosts" - Hosts are a list of hosts included in the TLS certificate. The values in this list must match the name/s used in the tlsSecret. Defaults to the wildcard host setting for the loadbalancer controller fulfilling this Ingress, if left unspecified.
  , networkingV1beta1IngressTLSSecretName :: !(Maybe Text) -- ^ "secretName" - SecretName is the name of the secret used to terminate SSL traffic on 443. Field is left optional to allow SSL routing based on SNI hostname alone. If the SNI host in a listener conflicts with the \&quot;Host\&quot; header field used by an IngressRule, the SNI host is used for termination and value of the Host header is used for routing.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON NetworkingV1beta1IngressTLS
instance A.FromJSON NetworkingV1beta1IngressTLS where
  parseJSON = A.withObject "NetworkingV1beta1IngressTLS" $ \o ->
    NetworkingV1beta1IngressTLS
      <$> (o .:? "hosts")
      <*> (o .:? "secretName")

-- | ToJSON NetworkingV1beta1IngressTLS
instance A.ToJSON NetworkingV1beta1IngressTLS where
  toJSON NetworkingV1beta1IngressTLS {..} =
   _omitNulls
      [ "hosts" .= networkingV1beta1IngressTLSHosts
      , "secretName" .= networkingV1beta1IngressTLSSecretName
      ]


-- | Construct a value of type 'NetworkingV1beta1IngressTLS' (by applying it's required fields, if any)
mkNetworkingV1beta1IngressTLS
  :: NetworkingV1beta1IngressTLS
mkNetworkingV1beta1IngressTLS =
  NetworkingV1beta1IngressTLS
  { networkingV1beta1IngressTLSHosts = Nothing
  , networkingV1beta1IngressTLSSecretName = Nothing
  }

-- ** PolicyV1beta1AllowedCSIDriver
-- | PolicyV1beta1AllowedCSIDriver
-- AllowedCSIDriver represents a single inline CSI Driver that is allowed to be used.
data PolicyV1beta1AllowedCSIDriver = PolicyV1beta1AllowedCSIDriver
  { policyV1beta1AllowedCSIDriverName :: !(Text) -- ^ /Required/ "name" - Name is the registered name of the CSI driver
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1AllowedCSIDriver
instance A.FromJSON PolicyV1beta1AllowedCSIDriver where
  parseJSON = A.withObject "PolicyV1beta1AllowedCSIDriver" $ \o ->
    PolicyV1beta1AllowedCSIDriver
      <$> (o .:  "name")

-- | ToJSON PolicyV1beta1AllowedCSIDriver
instance A.ToJSON PolicyV1beta1AllowedCSIDriver where
  toJSON PolicyV1beta1AllowedCSIDriver {..} =
   _omitNulls
      [ "name" .= policyV1beta1AllowedCSIDriverName
      ]


-- | Construct a value of type 'PolicyV1beta1AllowedCSIDriver' (by applying it's required fields, if any)
mkPolicyV1beta1AllowedCSIDriver
  :: Text -- ^ 'policyV1beta1AllowedCSIDriverName': Name is the registered name of the CSI driver
  -> PolicyV1beta1AllowedCSIDriver
mkPolicyV1beta1AllowedCSIDriver policyV1beta1AllowedCSIDriverName =
  PolicyV1beta1AllowedCSIDriver
  { policyV1beta1AllowedCSIDriverName
  }

-- ** PolicyV1beta1AllowedFlexVolume
-- | PolicyV1beta1AllowedFlexVolume
-- AllowedFlexVolume represents a single Flexvolume that is allowed to be used.
data PolicyV1beta1AllowedFlexVolume = PolicyV1beta1AllowedFlexVolume
  { policyV1beta1AllowedFlexVolumeDriver :: !(Text) -- ^ /Required/ "driver" - driver is the name of the Flexvolume driver.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1AllowedFlexVolume
instance A.FromJSON PolicyV1beta1AllowedFlexVolume where
  parseJSON = A.withObject "PolicyV1beta1AllowedFlexVolume" $ \o ->
    PolicyV1beta1AllowedFlexVolume
      <$> (o .:  "driver")

-- | ToJSON PolicyV1beta1AllowedFlexVolume
instance A.ToJSON PolicyV1beta1AllowedFlexVolume where
  toJSON PolicyV1beta1AllowedFlexVolume {..} =
   _omitNulls
      [ "driver" .= policyV1beta1AllowedFlexVolumeDriver
      ]


-- | Construct a value of type 'PolicyV1beta1AllowedFlexVolume' (by applying it's required fields, if any)
mkPolicyV1beta1AllowedFlexVolume
  :: Text -- ^ 'policyV1beta1AllowedFlexVolumeDriver': driver is the name of the Flexvolume driver.
  -> PolicyV1beta1AllowedFlexVolume
mkPolicyV1beta1AllowedFlexVolume policyV1beta1AllowedFlexVolumeDriver =
  PolicyV1beta1AllowedFlexVolume
  { policyV1beta1AllowedFlexVolumeDriver
  }

-- ** PolicyV1beta1AllowedHostPath
-- | PolicyV1beta1AllowedHostPath
-- AllowedHostPath defines the host volume conditions that will be enabled by a policy for pods to use. It requires the path prefix to be defined.
data PolicyV1beta1AllowedHostPath = PolicyV1beta1AllowedHostPath
  { policyV1beta1AllowedHostPathPathPrefix :: !(Maybe Text) -- ^ "pathPrefix" - pathPrefix is the path prefix that the host volume must match. It does not support &#x60;*&#x60;. Trailing slashes are trimmed when validating the path prefix with a host path.  Examples: &#x60;/foo&#x60; would allow &#x60;/foo&#x60;, &#x60;/foo/&#x60; and &#x60;/foo/bar&#x60; &#x60;/foo&#x60; would not allow &#x60;/food&#x60; or &#x60;/etc/foo&#x60;
  , policyV1beta1AllowedHostPathReadOnly :: !(Maybe Bool) -- ^ "readOnly" - when set to true, will allow host volumes matching the pathPrefix only if all volume mounts are readOnly.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1AllowedHostPath
instance A.FromJSON PolicyV1beta1AllowedHostPath where
  parseJSON = A.withObject "PolicyV1beta1AllowedHostPath" $ \o ->
    PolicyV1beta1AllowedHostPath
      <$> (o .:? "pathPrefix")
      <*> (o .:? "readOnly")

-- | ToJSON PolicyV1beta1AllowedHostPath
instance A.ToJSON PolicyV1beta1AllowedHostPath where
  toJSON PolicyV1beta1AllowedHostPath {..} =
   _omitNulls
      [ "pathPrefix" .= policyV1beta1AllowedHostPathPathPrefix
      , "readOnly" .= policyV1beta1AllowedHostPathReadOnly
      ]


-- | Construct a value of type 'PolicyV1beta1AllowedHostPath' (by applying it's required fields, if any)
mkPolicyV1beta1AllowedHostPath
  :: PolicyV1beta1AllowedHostPath
mkPolicyV1beta1AllowedHostPath =
  PolicyV1beta1AllowedHostPath
  { policyV1beta1AllowedHostPathPathPrefix = Nothing
  , policyV1beta1AllowedHostPathReadOnly = Nothing
  }

-- ** PolicyV1beta1FSGroupStrategyOptions
-- | PolicyV1beta1FSGroupStrategyOptions
-- FSGroupStrategyOptions defines the strategy type and options used to create the strategy.
data PolicyV1beta1FSGroupStrategyOptions = PolicyV1beta1FSGroupStrategyOptions
  { policyV1beta1FSGroupStrategyOptionsRanges :: !(Maybe [PolicyV1beta1IDRange]) -- ^ "ranges" - ranges are the allowed ranges of fs groups.  If you would like to force a single fs group then supply a single range with the same start and end. Required for MustRunAs.
  , policyV1beta1FSGroupStrategyOptionsRule :: !(Maybe Text) -- ^ "rule" - rule is the strategy that will dictate what FSGroup is used in the SecurityContext.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1FSGroupStrategyOptions
instance A.FromJSON PolicyV1beta1FSGroupStrategyOptions where
  parseJSON = A.withObject "PolicyV1beta1FSGroupStrategyOptions" $ \o ->
    PolicyV1beta1FSGroupStrategyOptions
      <$> (o .:? "ranges")
      <*> (o .:? "rule")

-- | ToJSON PolicyV1beta1FSGroupStrategyOptions
instance A.ToJSON PolicyV1beta1FSGroupStrategyOptions where
  toJSON PolicyV1beta1FSGroupStrategyOptions {..} =
   _omitNulls
      [ "ranges" .= policyV1beta1FSGroupStrategyOptionsRanges
      , "rule" .= policyV1beta1FSGroupStrategyOptionsRule
      ]


-- | Construct a value of type 'PolicyV1beta1FSGroupStrategyOptions' (by applying it's required fields, if any)
mkPolicyV1beta1FSGroupStrategyOptions
  :: PolicyV1beta1FSGroupStrategyOptions
mkPolicyV1beta1FSGroupStrategyOptions =
  PolicyV1beta1FSGroupStrategyOptions
  { policyV1beta1FSGroupStrategyOptionsRanges = Nothing
  , policyV1beta1FSGroupStrategyOptionsRule = Nothing
  }

-- ** PolicyV1beta1HostPortRange
-- | PolicyV1beta1HostPortRange
-- HostPortRange defines a range of host ports that will be enabled by a policy for pods to use.  It requires both the start and end to be defined.
data PolicyV1beta1HostPortRange = PolicyV1beta1HostPortRange
  { policyV1beta1HostPortRangeMax :: !(Int) -- ^ /Required/ "max" - max is the end of the range, inclusive.
  , policyV1beta1HostPortRangeMin :: !(Int) -- ^ /Required/ "min" - min is the start of the range, inclusive.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1HostPortRange
instance A.FromJSON PolicyV1beta1HostPortRange where
  parseJSON = A.withObject "PolicyV1beta1HostPortRange" $ \o ->
    PolicyV1beta1HostPortRange
      <$> (o .:  "max")
      <*> (o .:  "min")

-- | ToJSON PolicyV1beta1HostPortRange
instance A.ToJSON PolicyV1beta1HostPortRange where
  toJSON PolicyV1beta1HostPortRange {..} =
   _omitNulls
      [ "max" .= policyV1beta1HostPortRangeMax
      , "min" .= policyV1beta1HostPortRangeMin
      ]


-- | Construct a value of type 'PolicyV1beta1HostPortRange' (by applying it's required fields, if any)
mkPolicyV1beta1HostPortRange
  :: Int -- ^ 'policyV1beta1HostPortRangeMax': max is the end of the range, inclusive.
  -> Int -- ^ 'policyV1beta1HostPortRangeMin': min is the start of the range, inclusive.
  -> PolicyV1beta1HostPortRange
mkPolicyV1beta1HostPortRange policyV1beta1HostPortRangeMax policyV1beta1HostPortRangeMin =
  PolicyV1beta1HostPortRange
  { policyV1beta1HostPortRangeMax
  , policyV1beta1HostPortRangeMin
  }

-- ** PolicyV1beta1IDRange
-- | PolicyV1beta1IDRange
-- IDRange provides a min/max of an allowed range of IDs.
data PolicyV1beta1IDRange = PolicyV1beta1IDRange
  { policyV1beta1IDRangeMax :: !(Integer) -- ^ /Required/ "max" - max is the end of the range, inclusive.
  , policyV1beta1IDRangeMin :: !(Integer) -- ^ /Required/ "min" - min is the start of the range, inclusive.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1IDRange
instance A.FromJSON PolicyV1beta1IDRange where
  parseJSON = A.withObject "PolicyV1beta1IDRange" $ \o ->
    PolicyV1beta1IDRange
      <$> (o .:  "max")
      <*> (o .:  "min")

-- | ToJSON PolicyV1beta1IDRange
instance A.ToJSON PolicyV1beta1IDRange where
  toJSON PolicyV1beta1IDRange {..} =
   _omitNulls
      [ "max" .= policyV1beta1IDRangeMax
      , "min" .= policyV1beta1IDRangeMin
      ]


-- | Construct a value of type 'PolicyV1beta1IDRange' (by applying it's required fields, if any)
mkPolicyV1beta1IDRange
  :: Integer -- ^ 'policyV1beta1IDRangeMax': max is the end of the range, inclusive.
  -> Integer -- ^ 'policyV1beta1IDRangeMin': min is the start of the range, inclusive.
  -> PolicyV1beta1IDRange
mkPolicyV1beta1IDRange policyV1beta1IDRangeMax policyV1beta1IDRangeMin =
  PolicyV1beta1IDRange
  { policyV1beta1IDRangeMax
  , policyV1beta1IDRangeMin
  }

-- ** PolicyV1beta1PodSecurityPolicy
-- | PolicyV1beta1PodSecurityPolicy
-- PodSecurityPolicy governs the ability to make requests that affect the Security Context that will be applied to a pod and container.
data PolicyV1beta1PodSecurityPolicy = PolicyV1beta1PodSecurityPolicy
  { policyV1beta1PodSecurityPolicyApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , policyV1beta1PodSecurityPolicyKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , policyV1beta1PodSecurityPolicyMetadata :: !(Maybe V1ObjectMeta) -- ^ "metadata"
  , policyV1beta1PodSecurityPolicySpec :: !(Maybe PolicyV1beta1PodSecurityPolicySpec) -- ^ "spec"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1PodSecurityPolicy
instance A.FromJSON PolicyV1beta1PodSecurityPolicy where
  parseJSON = A.withObject "PolicyV1beta1PodSecurityPolicy" $ \o ->
    PolicyV1beta1PodSecurityPolicy
      <$> (o .:? "apiVersion")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")
      <*> (o .:? "spec")

-- | ToJSON PolicyV1beta1PodSecurityPolicy
instance A.ToJSON PolicyV1beta1PodSecurityPolicy where
  toJSON PolicyV1beta1PodSecurityPolicy {..} =
   _omitNulls
      [ "apiVersion" .= policyV1beta1PodSecurityPolicyApiVersion
      , "kind" .= policyV1beta1PodSecurityPolicyKind
      , "metadata" .= policyV1beta1PodSecurityPolicyMetadata
      , "spec" .= policyV1beta1PodSecurityPolicySpec
      ]


-- | Construct a value of type 'PolicyV1beta1PodSecurityPolicy' (by applying it's required fields, if any)
mkPolicyV1beta1PodSecurityPolicy
  :: PolicyV1beta1PodSecurityPolicy
mkPolicyV1beta1PodSecurityPolicy =
  PolicyV1beta1PodSecurityPolicy
  { policyV1beta1PodSecurityPolicyApiVersion = Nothing
  , policyV1beta1PodSecurityPolicyKind = Nothing
  , policyV1beta1PodSecurityPolicyMetadata = Nothing
  , policyV1beta1PodSecurityPolicySpec = Nothing
  }

-- ** PolicyV1beta1PodSecurityPolicyList
-- | PolicyV1beta1PodSecurityPolicyList
-- PodSecurityPolicyList is a list of PodSecurityPolicy objects.
data PolicyV1beta1PodSecurityPolicyList = PolicyV1beta1PodSecurityPolicyList
  { policyV1beta1PodSecurityPolicyListApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , policyV1beta1PodSecurityPolicyListItems :: !([PolicyV1beta1PodSecurityPolicy]) -- ^ /Required/ "items" - items is a list of schema objects.
  , policyV1beta1PodSecurityPolicyListKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , policyV1beta1PodSecurityPolicyListMetadata :: !(Maybe V1ListMeta) -- ^ "metadata"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1PodSecurityPolicyList
instance A.FromJSON PolicyV1beta1PodSecurityPolicyList where
  parseJSON = A.withObject "PolicyV1beta1PodSecurityPolicyList" $ \o ->
    PolicyV1beta1PodSecurityPolicyList
      <$> (o .:? "apiVersion")
      <*> (o .:  "items")
      <*> (o .:? "kind")
      <*> (o .:? "metadata")

-- | ToJSON PolicyV1beta1PodSecurityPolicyList
instance A.ToJSON PolicyV1beta1PodSecurityPolicyList where
  toJSON PolicyV1beta1PodSecurityPolicyList {..} =
   _omitNulls
      [ "apiVersion" .= policyV1beta1PodSecurityPolicyListApiVersion
      , "items" .= policyV1beta1PodSecurityPolicyListItems
      , "kind" .= policyV1beta1PodSecurityPolicyListKind
      , "metadata" .= policyV1beta1PodSecurityPolicyListMetadata
      ]


-- | Construct a value of type 'PolicyV1beta1PodSecurityPolicyList' (by applying it's required fields, if any)
mkPolicyV1beta1PodSecurityPolicyList
  :: [PolicyV1beta1PodSecurityPolicy] -- ^ 'policyV1beta1PodSecurityPolicyListItems': items is a list of schema objects.
  -> PolicyV1beta1PodSecurityPolicyList
mkPolicyV1beta1PodSecurityPolicyList policyV1beta1PodSecurityPolicyListItems =
  PolicyV1beta1PodSecurityPolicyList
  { policyV1beta1PodSecurityPolicyListApiVersion = Nothing
  , policyV1beta1PodSecurityPolicyListItems
  , policyV1beta1PodSecurityPolicyListKind = Nothing
  , policyV1beta1PodSecurityPolicyListMetadata = Nothing
  }

-- ** PolicyV1beta1PodSecurityPolicySpec
-- | PolicyV1beta1PodSecurityPolicySpec
-- PodSecurityPolicySpec defines the policy enforced.
data PolicyV1beta1PodSecurityPolicySpec = PolicyV1beta1PodSecurityPolicySpec
  { policyV1beta1PodSecurityPolicySpecAllowPrivilegeEscalation :: !(Maybe Bool) -- ^ "allowPrivilegeEscalation" - allowPrivilegeEscalation determines if a pod can request to allow privilege escalation. If unspecified, defaults to true.
  , policyV1beta1PodSecurityPolicySpecAllowedCsiDrivers :: !(Maybe [PolicyV1beta1AllowedCSIDriver]) -- ^ "allowedCSIDrivers" - AllowedCSIDrivers is a whitelist of inline CSI drivers that must be explicitly set to be embedded within a pod spec. An empty value indicates that any CSI driver can be used for inline ephemeral volumes. This is an alpha field, and is only honored if the API server enables the CSIInlineVolume feature gate.
  , policyV1beta1PodSecurityPolicySpecAllowedCapabilities :: !(Maybe [Text]) -- ^ "allowedCapabilities" - allowedCapabilities is a list of capabilities that can be requested to add to the container. Capabilities in this field may be added at the pod author&#39;s discretion. You must not list a capability in both allowedCapabilities and requiredDropCapabilities.
  , policyV1beta1PodSecurityPolicySpecAllowedFlexVolumes :: !(Maybe [PolicyV1beta1AllowedFlexVolume]) -- ^ "allowedFlexVolumes" - allowedFlexVolumes is a whitelist of allowed Flexvolumes.  Empty or nil indicates that all Flexvolumes may be used.  This parameter is effective only when the usage of the Flexvolumes is allowed in the \&quot;volumes\&quot; field.
  , policyV1beta1PodSecurityPolicySpecAllowedHostPaths :: !(Maybe [PolicyV1beta1AllowedHostPath]) -- ^ "allowedHostPaths" - allowedHostPaths is a white list of allowed host paths. Empty indicates that all host paths may be used.
  , policyV1beta1PodSecurityPolicySpecAllowedProcMountTypes :: !(Maybe [Text]) -- ^ "allowedProcMountTypes" - AllowedProcMountTypes is a whitelist of allowed ProcMountTypes. Empty or nil indicates that only the DefaultProcMountType may be used. This requires the ProcMountType feature flag to be enabled.
  , policyV1beta1PodSecurityPolicySpecAllowedUnsafeSysctls :: !(Maybe [Text]) -- ^ "allowedUnsafeSysctls" - allowedUnsafeSysctls is a list of explicitly allowed unsafe sysctls, defaults to none. Each entry is either a plain sysctl name or ends in \&quot;*\&quot; in which case it is considered as a prefix of allowed sysctls. Single * means all unsafe sysctls are allowed. Kubelet has to whitelist all allowed unsafe sysctls explicitly to avoid rejection.  Examples: e.g. \&quot;foo/*\&quot; allows \&quot;foo/bar\&quot;, \&quot;foo/baz\&quot;, etc. e.g. \&quot;foo.*\&quot; allows \&quot;foo.bar\&quot;, \&quot;foo.baz\&quot;, etc.
  , policyV1beta1PodSecurityPolicySpecDefaultAddCapabilities :: !(Maybe [Text]) -- ^ "defaultAddCapabilities" - defaultAddCapabilities is the default set of capabilities that will be added to the container unless the pod spec specifically drops the capability.  You may not list a capability in both defaultAddCapabilities and requiredDropCapabilities. Capabilities added here are implicitly allowed, and need not be included in the allowedCapabilities list.
  , policyV1beta1PodSecurityPolicySpecDefaultAllowPrivilegeEscalation :: !(Maybe Bool) -- ^ "defaultAllowPrivilegeEscalation" - defaultAllowPrivilegeEscalation controls the default setting for whether a process can gain more privileges than its parent process.
  , policyV1beta1PodSecurityPolicySpecForbiddenSysctls :: !(Maybe [Text]) -- ^ "forbiddenSysctls" - forbiddenSysctls is a list of explicitly forbidden sysctls, defaults to none. Each entry is either a plain sysctl name or ends in \&quot;*\&quot; in which case it is considered as a prefix of forbidden sysctls. Single * means all sysctls are forbidden.  Examples: e.g. \&quot;foo/*\&quot; forbids \&quot;foo/bar\&quot;, \&quot;foo/baz\&quot;, etc. e.g. \&quot;foo.*\&quot; forbids \&quot;foo.bar\&quot;, \&quot;foo.baz\&quot;, etc.
  , policyV1beta1PodSecurityPolicySpecFsGroup :: !(PolicyV1beta1FSGroupStrategyOptions) -- ^ /Required/ "fsGroup"
  , policyV1beta1PodSecurityPolicySpecHostIpc :: !(Maybe Bool) -- ^ "hostIPC" - hostIPC determines if the policy allows the use of HostIPC in the pod spec.
  , policyV1beta1PodSecurityPolicySpecHostNetwork :: !(Maybe Bool) -- ^ "hostNetwork" - hostNetwork determines if the policy allows the use of HostNetwork in the pod spec.
  , policyV1beta1PodSecurityPolicySpecHostPid :: !(Maybe Bool) -- ^ "hostPID" - hostPID determines if the policy allows the use of HostPID in the pod spec.
  , policyV1beta1PodSecurityPolicySpecHostPorts :: !(Maybe [PolicyV1beta1HostPortRange]) -- ^ "hostPorts" - hostPorts determines which host port ranges are allowed to be exposed.
  , policyV1beta1PodSecurityPolicySpecPrivileged :: !(Maybe Bool) -- ^ "privileged" - privileged determines if a pod can request to be run as privileged.
  , policyV1beta1PodSecurityPolicySpecReadOnlyRootFilesystem :: !(Maybe Bool) -- ^ "readOnlyRootFilesystem" - readOnlyRootFilesystem when set to true will force containers to run with a read only root file system.  If the container specifically requests to run with a non-read only root file system the PSP should deny the pod. If set to false the container may run with a read only root file system if it wishes but it will not be forced to.
  , policyV1beta1PodSecurityPolicySpecRequiredDropCapabilities :: !(Maybe [Text]) -- ^ "requiredDropCapabilities" - requiredDropCapabilities are the capabilities that will be dropped from the container.  These are required to be dropped and cannot be added.
  , policyV1beta1PodSecurityPolicySpecRunAsGroup :: !(Maybe PolicyV1beta1RunAsGroupStrategyOptions) -- ^ "runAsGroup"
  , policyV1beta1PodSecurityPolicySpecRunAsUser :: !(PolicyV1beta1RunAsUserStrategyOptions) -- ^ /Required/ "runAsUser"
  , policyV1beta1PodSecurityPolicySpecRuntimeClass :: !(Maybe PolicyV1beta1RuntimeClassStrategyOptions) -- ^ "runtimeClass"
  , policyV1beta1PodSecurityPolicySpecSeLinux :: !(PolicyV1beta1SELinuxStrategyOptions) -- ^ /Required/ "seLinux"
  , policyV1beta1PodSecurityPolicySpecSupplementalGroups :: !(PolicyV1beta1SupplementalGroupsStrategyOptions) -- ^ /Required/ "supplementalGroups"
  , policyV1beta1PodSecurityPolicySpecVolumes :: !(Maybe [Text]) -- ^ "volumes" - volumes is a white list of allowed volume plugins. Empty indicates that no volumes may be used. To allow all volumes you may use &#39;*&#39;.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1PodSecurityPolicySpec
instance A.FromJSON PolicyV1beta1PodSecurityPolicySpec where
  parseJSON = A.withObject "PolicyV1beta1PodSecurityPolicySpec" $ \o ->
    PolicyV1beta1PodSecurityPolicySpec
      <$> (o .:? "allowPrivilegeEscalation")
      <*> (o .:? "allowedCSIDrivers")
      <*> (o .:? "allowedCapabilities")
      <*> (o .:? "allowedFlexVolumes")
      <*> (o .:? "allowedHostPaths")
      <*> (o .:? "allowedProcMountTypes")
      <*> (o .:? "allowedUnsafeSysctls")
      <*> (o .:? "defaultAddCapabilities")
      <*> (o .:? "defaultAllowPrivilegeEscalation")
      <*> (o .:? "forbiddenSysctls")
      <*> (o .:  "fsGroup")
      <*> (o .:? "hostIPC")
      <*> (o .:? "hostNetwork")
      <*> (o .:? "hostPID")
      <*> (o .:? "hostPorts")
      <*> (o .:? "privileged")
      <*> (o .:? "readOnlyRootFilesystem")
      <*> (o .:? "requiredDropCapabilities")
      <*> (o .:? "runAsGroup")
      <*> (o .:  "runAsUser")
      <*> (o .:? "runtimeClass")
      <*> (o .:  "seLinux")
      <*> (o .:  "supplementalGroups")
      <*> (o .:? "volumes")

-- | ToJSON PolicyV1beta1PodSecurityPolicySpec
instance A.ToJSON PolicyV1beta1PodSecurityPolicySpec where
  toJSON PolicyV1beta1PodSecurityPolicySpec {..} =
   _omitNulls
      [ "allowPrivilegeEscalation" .= policyV1beta1PodSecurityPolicySpecAllowPrivilegeEscalation
      , "allowedCSIDrivers" .= policyV1beta1PodSecurityPolicySpecAllowedCsiDrivers
      , "allowedCapabilities" .= policyV1beta1PodSecurityPolicySpecAllowedCapabilities
      , "allowedFlexVolumes" .= policyV1beta1PodSecurityPolicySpecAllowedFlexVolumes
      , "allowedHostPaths" .= policyV1beta1PodSecurityPolicySpecAllowedHostPaths
      , "allowedProcMountTypes" .= policyV1beta1PodSecurityPolicySpecAllowedProcMountTypes
      , "allowedUnsafeSysctls" .= policyV1beta1PodSecurityPolicySpecAllowedUnsafeSysctls
      , "defaultAddCapabilities" .= policyV1beta1PodSecurityPolicySpecDefaultAddCapabilities
      , "defaultAllowPrivilegeEscalation" .= policyV1beta1PodSecurityPolicySpecDefaultAllowPrivilegeEscalation
      , "forbiddenSysctls" .= policyV1beta1PodSecurityPolicySpecForbiddenSysctls
      , "fsGroup" .= policyV1beta1PodSecurityPolicySpecFsGroup
      , "hostIPC" .= policyV1beta1PodSecurityPolicySpecHostIpc
      , "hostNetwork" .= policyV1beta1PodSecurityPolicySpecHostNetwork
      , "hostPID" .= policyV1beta1PodSecurityPolicySpecHostPid
      , "hostPorts" .= policyV1beta1PodSecurityPolicySpecHostPorts
      , "privileged" .= policyV1beta1PodSecurityPolicySpecPrivileged
      , "readOnlyRootFilesystem" .= policyV1beta1PodSecurityPolicySpecReadOnlyRootFilesystem
      , "requiredDropCapabilities" .= policyV1beta1PodSecurityPolicySpecRequiredDropCapabilities
      , "runAsGroup" .= policyV1beta1PodSecurityPolicySpecRunAsGroup
      , "runAsUser" .= policyV1beta1PodSecurityPolicySpecRunAsUser
      , "runtimeClass" .= policyV1beta1PodSecurityPolicySpecRuntimeClass
      , "seLinux" .= policyV1beta1PodSecurityPolicySpecSeLinux
      , "supplementalGroups" .= policyV1beta1PodSecurityPolicySpecSupplementalGroups
      , "volumes" .= policyV1beta1PodSecurityPolicySpecVolumes
      ]


-- | Construct a value of type 'PolicyV1beta1PodSecurityPolicySpec' (by applying it's required fields, if any)
mkPolicyV1beta1PodSecurityPolicySpec
  :: PolicyV1beta1FSGroupStrategyOptions -- ^ 'policyV1beta1PodSecurityPolicySpecFsGroup' 
  -> PolicyV1beta1RunAsUserStrategyOptions -- ^ 'policyV1beta1PodSecurityPolicySpecRunAsUser' 
  -> PolicyV1beta1SELinuxStrategyOptions -- ^ 'policyV1beta1PodSecurityPolicySpecSeLinux' 
  -> PolicyV1beta1SupplementalGroupsStrategyOptions -- ^ 'policyV1beta1PodSecurityPolicySpecSupplementalGroups' 
  -> PolicyV1beta1PodSecurityPolicySpec
mkPolicyV1beta1PodSecurityPolicySpec policyV1beta1PodSecurityPolicySpecFsGroup policyV1beta1PodSecurityPolicySpecRunAsUser policyV1beta1PodSecurityPolicySpecSeLinux policyV1beta1PodSecurityPolicySpecSupplementalGroups =
  PolicyV1beta1PodSecurityPolicySpec
  { policyV1beta1PodSecurityPolicySpecAllowPrivilegeEscalation = Nothing
  , policyV1beta1PodSecurityPolicySpecAllowedCsiDrivers = Nothing
  , policyV1beta1PodSecurityPolicySpecAllowedCapabilities = Nothing
  , policyV1beta1PodSecurityPolicySpecAllowedFlexVolumes = Nothing
  , policyV1beta1PodSecurityPolicySpecAllowedHostPaths = Nothing
  , policyV1beta1PodSecurityPolicySpecAllowedProcMountTypes = Nothing
  , policyV1beta1PodSecurityPolicySpecAllowedUnsafeSysctls = Nothing
  , policyV1beta1PodSecurityPolicySpecDefaultAddCapabilities = Nothing
  , policyV1beta1PodSecurityPolicySpecDefaultAllowPrivilegeEscalation = Nothing
  , policyV1beta1PodSecurityPolicySpecForbiddenSysctls = Nothing
  , policyV1beta1PodSecurityPolicySpecFsGroup
  , policyV1beta1PodSecurityPolicySpecHostIpc = Nothing
  , policyV1beta1PodSecurityPolicySpecHostNetwork = Nothing
  , policyV1beta1PodSecurityPolicySpecHostPid = Nothing
  , policyV1beta1PodSecurityPolicySpecHostPorts = Nothing
  , policyV1beta1PodSecurityPolicySpecPrivileged = Nothing
  , policyV1beta1PodSecurityPolicySpecReadOnlyRootFilesystem = Nothing
  , policyV1beta1PodSecurityPolicySpecRequiredDropCapabilities = Nothing
  , policyV1beta1PodSecurityPolicySpecRunAsGroup = Nothing
  , policyV1beta1PodSecurityPolicySpecRunAsUser
  , policyV1beta1PodSecurityPolicySpecRuntimeClass = Nothing
  , policyV1beta1PodSecurityPolicySpecSeLinux
  , policyV1beta1PodSecurityPolicySpecSupplementalGroups
  , policyV1beta1PodSecurityPolicySpecVolumes = Nothing
  }

-- ** PolicyV1beta1RunAsGroupStrategyOptions
-- | PolicyV1beta1RunAsGroupStrategyOptions
-- RunAsGroupStrategyOptions defines the strategy type and any options used to create the strategy.
data PolicyV1beta1RunAsGroupStrategyOptions = PolicyV1beta1RunAsGroupStrategyOptions
  { policyV1beta1RunAsGroupStrategyOptionsRanges :: !(Maybe [PolicyV1beta1IDRange]) -- ^ "ranges" - ranges are the allowed ranges of gids that may be used. If you would like to force a single gid then supply a single range with the same start and end. Required for MustRunAs.
  , policyV1beta1RunAsGroupStrategyOptionsRule :: !(Text) -- ^ /Required/ "rule" - rule is the strategy that will dictate the allowable RunAsGroup values that may be set.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1RunAsGroupStrategyOptions
instance A.FromJSON PolicyV1beta1RunAsGroupStrategyOptions where
  parseJSON = A.withObject "PolicyV1beta1RunAsGroupStrategyOptions" $ \o ->
    PolicyV1beta1RunAsGroupStrategyOptions
      <$> (o .:? "ranges")
      <*> (o .:  "rule")

-- | ToJSON PolicyV1beta1RunAsGroupStrategyOptions
instance A.ToJSON PolicyV1beta1RunAsGroupStrategyOptions where
  toJSON PolicyV1beta1RunAsGroupStrategyOptions {..} =
   _omitNulls
      [ "ranges" .= policyV1beta1RunAsGroupStrategyOptionsRanges
      , "rule" .= policyV1beta1RunAsGroupStrategyOptionsRule
      ]


-- | Construct a value of type 'PolicyV1beta1RunAsGroupStrategyOptions' (by applying it's required fields, if any)
mkPolicyV1beta1RunAsGroupStrategyOptions
  :: Text -- ^ 'policyV1beta1RunAsGroupStrategyOptionsRule': rule is the strategy that will dictate the allowable RunAsGroup values that may be set.
  -> PolicyV1beta1RunAsGroupStrategyOptions
mkPolicyV1beta1RunAsGroupStrategyOptions policyV1beta1RunAsGroupStrategyOptionsRule =
  PolicyV1beta1RunAsGroupStrategyOptions
  { policyV1beta1RunAsGroupStrategyOptionsRanges = Nothing
  , policyV1beta1RunAsGroupStrategyOptionsRule
  }

-- ** PolicyV1beta1RunAsUserStrategyOptions
-- | PolicyV1beta1RunAsUserStrategyOptions
-- RunAsUserStrategyOptions defines the strategy type and any options used to create the strategy.
data PolicyV1beta1RunAsUserStrategyOptions = PolicyV1beta1RunAsUserStrategyOptions
  { policyV1beta1RunAsUserStrategyOptionsRanges :: !(Maybe [PolicyV1beta1IDRange]) -- ^ "ranges" - ranges are the allowed ranges of uids that may be used. If you would like to force a single uid then supply a single range with the same start and end. Required for MustRunAs.
  , policyV1beta1RunAsUserStrategyOptionsRule :: !(Text) -- ^ /Required/ "rule" - rule is the strategy that will dictate the allowable RunAsUser values that may be set.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1RunAsUserStrategyOptions
instance A.FromJSON PolicyV1beta1RunAsUserStrategyOptions where
  parseJSON = A.withObject "PolicyV1beta1RunAsUserStrategyOptions" $ \o ->
    PolicyV1beta1RunAsUserStrategyOptions
      <$> (o .:? "ranges")
      <*> (o .:  "rule")

-- | ToJSON PolicyV1beta1RunAsUserStrategyOptions
instance A.ToJSON PolicyV1beta1RunAsUserStrategyOptions where
  toJSON PolicyV1beta1RunAsUserStrategyOptions {..} =
   _omitNulls
      [ "ranges" .= policyV1beta1RunAsUserStrategyOptionsRanges
      , "rule" .= policyV1beta1RunAsUserStrategyOptionsRule
      ]


-- | Construct a value of type 'PolicyV1beta1RunAsUserStrategyOptions' (by applying it's required fields, if any)
mkPolicyV1beta1RunAsUserStrategyOptions
  :: Text -- ^ 'policyV1beta1RunAsUserStrategyOptionsRule': rule is the strategy that will dictate the allowable RunAsUser values that may be set.
  -> PolicyV1beta1RunAsUserStrategyOptions
mkPolicyV1beta1RunAsUserStrategyOptions policyV1beta1RunAsUserStrategyOptionsRule =
  PolicyV1beta1RunAsUserStrategyOptions
  { policyV1beta1RunAsUserStrategyOptionsRanges = Nothing
  , policyV1beta1RunAsUserStrategyOptionsRule
  }

-- ** PolicyV1beta1RuntimeClassStrategyOptions
-- | PolicyV1beta1RuntimeClassStrategyOptions
-- RuntimeClassStrategyOptions define the strategy that will dictate the allowable RuntimeClasses for a pod.
data PolicyV1beta1RuntimeClassStrategyOptions = PolicyV1beta1RuntimeClassStrategyOptions
  { policyV1beta1RuntimeClassStrategyOptionsAllowedRuntimeClassNames :: !([Text]) -- ^ /Required/ "allowedRuntimeClassNames" - allowedRuntimeClassNames is a whitelist of RuntimeClass names that may be specified on a pod. A value of \&quot;*\&quot; means that any RuntimeClass name is allowed, and must be the only item in the list. An empty list requires the RuntimeClassName field to be unset.
  , policyV1beta1RuntimeClassStrategyOptionsDefaultRuntimeClassName :: !(Maybe Text) -- ^ "defaultRuntimeClassName" - defaultRuntimeClassName is the default RuntimeClassName to set on the pod. The default MUST be allowed by the allowedRuntimeClassNames list. A value of nil does not mutate the Pod.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1RuntimeClassStrategyOptions
instance A.FromJSON PolicyV1beta1RuntimeClassStrategyOptions where
  parseJSON = A.withObject "PolicyV1beta1RuntimeClassStrategyOptions" $ \o ->
    PolicyV1beta1RuntimeClassStrategyOptions
      <$> (o .:  "allowedRuntimeClassNames")
      <*> (o .:? "defaultRuntimeClassName")

-- | ToJSON PolicyV1beta1RuntimeClassStrategyOptions
instance A.ToJSON PolicyV1beta1RuntimeClassStrategyOptions where
  toJSON PolicyV1beta1RuntimeClassStrategyOptions {..} =
   _omitNulls
      [ "allowedRuntimeClassNames" .= policyV1beta1RuntimeClassStrategyOptionsAllowedRuntimeClassNames
      , "defaultRuntimeClassName" .= policyV1beta1RuntimeClassStrategyOptionsDefaultRuntimeClassName
      ]


-- | Construct a value of type 'PolicyV1beta1RuntimeClassStrategyOptions' (by applying it's required fields, if any)
mkPolicyV1beta1RuntimeClassStrategyOptions
  :: [Text] -- ^ 'policyV1beta1RuntimeClassStrategyOptionsAllowedRuntimeClassNames': allowedRuntimeClassNames is a whitelist of RuntimeClass names that may be specified on a pod. A value of \"*\" means that any RuntimeClass name is allowed, and must be the only item in the list. An empty list requires the RuntimeClassName field to be unset.
  -> PolicyV1beta1RuntimeClassStrategyOptions
mkPolicyV1beta1RuntimeClassStrategyOptions policyV1beta1RuntimeClassStrategyOptionsAllowedRuntimeClassNames =
  PolicyV1beta1RuntimeClassStrategyOptions
  { policyV1beta1RuntimeClassStrategyOptionsAllowedRuntimeClassNames
  , policyV1beta1RuntimeClassStrategyOptionsDefaultRuntimeClassName = Nothing
  }

-- ** PolicyV1beta1SELinuxStrategyOptions
-- | PolicyV1beta1SELinuxStrategyOptions
-- SELinuxStrategyOptions defines the strategy type and any options used to create the strategy.
data PolicyV1beta1SELinuxStrategyOptions = PolicyV1beta1SELinuxStrategyOptions
  { policyV1beta1SELinuxStrategyOptionsRule :: !(Text) -- ^ /Required/ "rule" - rule is the strategy that will dictate the allowable labels that may be set.
  , policyV1beta1SELinuxStrategyOptionsSeLinuxOptions :: !(Maybe V1SELinuxOptions) -- ^ "seLinuxOptions"
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1SELinuxStrategyOptions
instance A.FromJSON PolicyV1beta1SELinuxStrategyOptions where
  parseJSON = A.withObject "PolicyV1beta1SELinuxStrategyOptions" $ \o ->
    PolicyV1beta1SELinuxStrategyOptions
      <$> (o .:  "rule")
      <*> (o .:? "seLinuxOptions")

-- | ToJSON PolicyV1beta1SELinuxStrategyOptions
instance A.ToJSON PolicyV1beta1SELinuxStrategyOptions where
  toJSON PolicyV1beta1SELinuxStrategyOptions {..} =
   _omitNulls
      [ "rule" .= policyV1beta1SELinuxStrategyOptionsRule
      , "seLinuxOptions" .= policyV1beta1SELinuxStrategyOptionsSeLinuxOptions
      ]


-- | Construct a value of type 'PolicyV1beta1SELinuxStrategyOptions' (by applying it's required fields, if any)
mkPolicyV1beta1SELinuxStrategyOptions
  :: Text -- ^ 'policyV1beta1SELinuxStrategyOptionsRule': rule is the strategy that will dictate the allowable labels that may be set.
  -> PolicyV1beta1SELinuxStrategyOptions
mkPolicyV1beta1SELinuxStrategyOptions policyV1beta1SELinuxStrategyOptionsRule =
  PolicyV1beta1SELinuxStrategyOptions
  { policyV1beta1SELinuxStrategyOptionsRule
  , policyV1beta1SELinuxStrategyOptionsSeLinuxOptions = Nothing
  }

-- ** PolicyV1beta1SupplementalGroupsStrategyOptions
-- | PolicyV1beta1SupplementalGroupsStrategyOptions
-- SupplementalGroupsStrategyOptions defines the strategy type and options used to create the strategy.
data PolicyV1beta1SupplementalGroupsStrategyOptions = PolicyV1beta1SupplementalGroupsStrategyOptions
  { policyV1beta1SupplementalGroupsStrategyOptionsRanges :: !(Maybe [PolicyV1beta1IDRange]) -- ^ "ranges" - ranges are the allowed ranges of supplemental groups.  If you would like to force a single supplemental group then supply a single range with the same start and end. Required for MustRunAs.
  , policyV1beta1SupplementalGroupsStrategyOptionsRule :: !(Maybe Text) -- ^ "rule" - rule is the strategy that will dictate what supplemental groups is used in the SecurityContext.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON PolicyV1beta1SupplementalGroupsStrategyOptions
instance A.FromJSON PolicyV1beta1SupplementalGroupsStrategyOptions where
  parseJSON = A.withObject "PolicyV1beta1SupplementalGroupsStrategyOptions" $ \o ->
    PolicyV1beta1SupplementalGroupsStrategyOptions
      <$> (o .:? "ranges")
      <*> (o .:? "rule")

-- | ToJSON PolicyV1beta1SupplementalGroupsStrategyOptions
instance A.ToJSON PolicyV1beta1SupplementalGroupsStrategyOptions where
  toJSON PolicyV1beta1SupplementalGroupsStrategyOptions {..} =
   _omitNulls
      [ "ranges" .= policyV1beta1SupplementalGroupsStrategyOptionsRanges
      , "rule" .= policyV1beta1SupplementalGroupsStrategyOptionsRule
      ]


-- | Construct a value of type 'PolicyV1beta1SupplementalGroupsStrategyOptions' (by applying it's required fields, if any)
mkPolicyV1beta1SupplementalGroupsStrategyOptions
  :: PolicyV1beta1SupplementalGroupsStrategyOptions
mkPolicyV1beta1SupplementalGroupsStrategyOptions =
  PolicyV1beta1SupplementalGroupsStrategyOptions
  { policyV1beta1SupplementalGroupsStrategyOptionsRanges = Nothing
  , policyV1beta1SupplementalGroupsStrategyOptionsRule = Nothing
  }

-- ** V1APIGroup
-- | V1APIGroup
-- APIGroup contains the name, the supported versions, and the preferred version of a group.
data V1APIGroup = V1APIGroup
  { v1APIGroupApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , v1APIGroupKind :: !(Maybe Text) -- ^ "kind" - Kind is a string value representing the REST resource this object represents. Servers may infer this from the endpoint the client submits requests to. Cannot be updated. In CamelCase. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#types-kinds
  , v1APIGroupName :: !(Text) -- ^ /Required/ "name" - name is the name of the group.
  , v1APIGroupPreferredVersion :: !(Maybe V1GroupVersionForDiscovery) -- ^ "preferredVersion"
  , v1APIGroupServerAddressByClientCidRs :: !(Maybe [V1ServerAddressByClientCIDR]) -- ^ "serverAddressByClientCIDRs" - a map of client CIDR to server address that is serving this group. This is to help clients reach servers in the most network-efficient way possible. Clients can use the appropriate server address as per the CIDR that they match. In case of multiple matches, clients should use the longest matching CIDR. The server returns only those CIDRs that it thinks that the client can match. For example: the master will return an internal IP CIDR only, if the client reaches the server using an internal IP. Server looks at X-Forwarded-For header or X-Real-Ip header or request.RemoteAddr (in that order) to get the client IP.
  , v1APIGroupVersions :: !([V1GroupVersionForDiscovery]) -- ^ /Required/ "versions" - versions are the versions supported in this group.
  } deriving (P.Show, P.Eq, P.Typeable)

-- | FromJSON V1APIGroup
instance A.FromJSON V1APIGroup where
  parseJSON = A.withObject "V1APIGroup" $ \o ->
    V1APIGroup
      <$> (o .:? "apiVersion")
      <*> (o .:? "kind")
      <*> (o .:  "name")
      <*> (o .:? "preferredVersion")
      <*> (o .:? "serverAddressByClientCIDRs")
      <*> (o .:  "versions")

-- | ToJSON V1APIGroup
instance A.ToJSON V1APIGroup where
  toJSON V1APIGroup {..} =
   _omitNulls
      [ "apiVersion" .= v1APIGroupApiVersion
      , "kind" .= v1APIGroupKind
      , "name" .= v1APIGroupName
      , "preferredVersion" .= v1APIGroupPreferredVersion
      , "serverAddressByClientCIDRs" .= v1APIGroupServerAddressByClientCidRs
      , "versions" .= v1APIGroupVersions
      ]


-- | Construct a value of type 'V1APIGroup' (by applying it's required fields, if any)
mkV1APIGroup
  :: Text -- ^ 'v1APIGroupName': name is the name of the group.
  -> [V1GroupVersionForDiscovery] -- ^ 'v1APIGroupVersions': versions are the versions supported in this group.
  -> V1APIGroup
mkV1APIGroup v1APIGroupName v1APIGroupVersions =
  V1APIGroup
  { v1APIGroupApiVersion = Nothing
  , v1APIGroupKind = Nothing
  , v1APIGroupName
  , v1APIGroupPreferredVersion = Nothing
  , v1APIGroupServerAddressByClientCidRs = Nothing
  , v1APIGroupVersions
  }

-- ** V1APIGroupList
-- | V1APIGroupList
-- APIGroupList is a list of APIGroup, to allow clients to discover the API at /apis.
data V1APIGroupList = V1APIGroupList
  { v1APIGroupListApiVersion :: !(Maybe Text) -- ^ "apiVersion" - APIVersion defines the versioned schema of this representation of an object. Servers should convert recognized schemas to the latest internal value, and may reject unrecognized values. More info: https://git.k8s.io/community/contributors/devel/sig-architecture/api-conventions.md#resources
  , v1APIGroupListGroups :: !([V1APIGroup]) -- ^ /Required/ "groups" - groups is a list of APIGroup.
  , v1APIGroupListKind :: !