module Stratosphere.Batch.JobDefinition.EksVolumeProperty (
module Exports, EksVolumeProperty(..), mkEksVolumeProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Batch.JobDefinition.EksEmptyDirProperty as Exports
import {-# SOURCE #-} Stratosphere.Batch.JobDefinition.EksHostPathProperty as Exports
import {-# SOURCE #-} Stratosphere.Batch.JobDefinition.EksPersistentVolumeClaimProperty as Exports
import {-# SOURCE #-} Stratosphere.Batch.JobDefinition.EksSecretProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data EksVolumeProperty
=
EksVolumeProperty {EksVolumeProperty -> ()
haddock_workaround_ :: (),
EksVolumeProperty -> Maybe EksEmptyDirProperty
emptyDir :: (Prelude.Maybe EksEmptyDirProperty),
EksVolumeProperty -> Maybe EksHostPathProperty
hostPath :: (Prelude.Maybe EksHostPathProperty),
EksVolumeProperty -> Value Text
name :: (Value Prelude.Text),
EksVolumeProperty -> Maybe EksPersistentVolumeClaimProperty
persistentVolumeClaim :: (Prelude.Maybe EksPersistentVolumeClaimProperty),
EksVolumeProperty -> Maybe EksSecretProperty
secret :: (Prelude.Maybe EksSecretProperty)}
deriving stock (EksVolumeProperty -> EksVolumeProperty -> Bool
(EksVolumeProperty -> EksVolumeProperty -> Bool)
-> (EksVolumeProperty -> EksVolumeProperty -> Bool)
-> Eq EksVolumeProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EksVolumeProperty -> EksVolumeProperty -> Bool
== :: EksVolumeProperty -> EksVolumeProperty -> Bool
$c/= :: EksVolumeProperty -> EksVolumeProperty -> Bool
/= :: EksVolumeProperty -> EksVolumeProperty -> Bool
Prelude.Eq, Int -> EksVolumeProperty -> ShowS
[EksVolumeProperty] -> ShowS
EksVolumeProperty -> String
(Int -> EksVolumeProperty -> ShowS)
-> (EksVolumeProperty -> String)
-> ([EksVolumeProperty] -> ShowS)
-> Show EksVolumeProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EksVolumeProperty -> ShowS
showsPrec :: Int -> EksVolumeProperty -> ShowS
$cshow :: EksVolumeProperty -> String
show :: EksVolumeProperty -> String
$cshowList :: [EksVolumeProperty] -> ShowS
showList :: [EksVolumeProperty] -> ShowS
Prelude.Show)
mkEksVolumeProperty :: Value Prelude.Text -> EksVolumeProperty
mkEksVolumeProperty :: Value Text -> EksVolumeProperty
mkEksVolumeProperty Value Text
name
= EksVolumeProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), name :: Value Text
name = Value Text
name, emptyDir :: Maybe EksEmptyDirProperty
emptyDir = Maybe EksEmptyDirProperty
forall a. Maybe a
Prelude.Nothing,
hostPath :: Maybe EksHostPathProperty
hostPath = Maybe EksHostPathProperty
forall a. Maybe a
Prelude.Nothing,
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
persistentVolumeClaim = Maybe EksPersistentVolumeClaimProperty
forall a. Maybe a
Prelude.Nothing, secret :: Maybe EksSecretProperty
secret = Maybe EksSecretProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties EksVolumeProperty where
toResourceProperties :: EksVolumeProperty -> ResourceProperties
toResourceProperties EksVolumeProperty {Maybe EksEmptyDirProperty
Maybe EksHostPathProperty
Maybe EksPersistentVolumeClaimProperty
Maybe EksSecretProperty
()
Value Text
haddock_workaround_ :: EksVolumeProperty -> ()
emptyDir :: EksVolumeProperty -> Maybe EksEmptyDirProperty
hostPath :: EksVolumeProperty -> Maybe EksHostPathProperty
name :: EksVolumeProperty -> Value Text
persistentVolumeClaim :: EksVolumeProperty -> Maybe EksPersistentVolumeClaimProperty
secret :: EksVolumeProperty -> Maybe EksSecretProperty
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Batch::JobDefinition.EksVolume",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Name" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
name]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> EksEmptyDirProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EmptyDir" (EksEmptyDirProperty -> (Key, Value))
-> Maybe EksEmptyDirProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EksEmptyDirProperty
emptyDir,
Key -> EksHostPathProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HostPath" (EksHostPathProperty -> (Key, Value))
-> Maybe EksHostPathProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EksHostPathProperty
hostPath,
Key -> EksPersistentVolumeClaimProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PersistentVolumeClaim"
(EksPersistentVolumeClaimProperty -> (Key, Value))
-> Maybe EksPersistentVolumeClaimProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EksPersistentVolumeClaimProperty
persistentVolumeClaim,
Key -> EksSecretProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Secret" (EksSecretProperty -> (Key, Value))
-> Maybe EksSecretProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EksSecretProperty
secret]))}
instance JSON.ToJSON EksVolumeProperty where
toJSON :: EksVolumeProperty -> Value
toJSON EksVolumeProperty {Maybe EksEmptyDirProperty
Maybe EksHostPathProperty
Maybe EksPersistentVolumeClaimProperty
Maybe EksSecretProperty
()
Value Text
haddock_workaround_ :: EksVolumeProperty -> ()
emptyDir :: EksVolumeProperty -> Maybe EksEmptyDirProperty
hostPath :: EksVolumeProperty -> Maybe EksHostPathProperty
name :: EksVolumeProperty -> Value Text
persistentVolumeClaim :: EksVolumeProperty -> Maybe EksPersistentVolumeClaimProperty
secret :: EksVolumeProperty -> Maybe EksSecretProperty
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Name" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
name]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> EksEmptyDirProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EmptyDir" (EksEmptyDirProperty -> (Key, Value))
-> Maybe EksEmptyDirProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EksEmptyDirProperty
emptyDir,
Key -> EksHostPathProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HostPath" (EksHostPathProperty -> (Key, Value))
-> Maybe EksHostPathProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EksHostPathProperty
hostPath,
Key -> EksPersistentVolumeClaimProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PersistentVolumeClaim"
(EksPersistentVolumeClaimProperty -> (Key, Value))
-> Maybe EksPersistentVolumeClaimProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EksPersistentVolumeClaimProperty
persistentVolumeClaim,
Key -> EksSecretProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Secret" (EksSecretProperty -> (Key, Value))
-> Maybe EksSecretProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EksSecretProperty
secret])))
instance Property "EmptyDir" EksVolumeProperty where
type PropertyType "EmptyDir" EksVolumeProperty = EksEmptyDirProperty
set :: PropertyType "EmptyDir" EksVolumeProperty
-> EksVolumeProperty -> EksVolumeProperty
set PropertyType "EmptyDir" EksVolumeProperty
newValue EksVolumeProperty {Maybe EksEmptyDirProperty
Maybe EksHostPathProperty
Maybe EksPersistentVolumeClaimProperty
Maybe EksSecretProperty
()
Value Text
haddock_workaround_ :: EksVolumeProperty -> ()
emptyDir :: EksVolumeProperty -> Maybe EksEmptyDirProperty
hostPath :: EksVolumeProperty -> Maybe EksHostPathProperty
name :: EksVolumeProperty -> Value Text
persistentVolumeClaim :: EksVolumeProperty -> Maybe EksPersistentVolumeClaimProperty
secret :: EksVolumeProperty -> Maybe EksSecretProperty
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
..}
= EksVolumeProperty {emptyDir :: Maybe EksEmptyDirProperty
emptyDir = EksEmptyDirProperty -> Maybe EksEmptyDirProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EmptyDir" EksVolumeProperty
EksEmptyDirProperty
newValue, Maybe EksHostPathProperty
Maybe EksPersistentVolumeClaimProperty
Maybe EksSecretProperty
()
Value Text
haddock_workaround_ :: ()
hostPath :: Maybe EksHostPathProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
haddock_workaround_ :: ()
hostPath :: Maybe EksHostPathProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
..}
instance Property "HostPath" EksVolumeProperty where
type PropertyType "HostPath" EksVolumeProperty = EksHostPathProperty
set :: PropertyType "HostPath" EksVolumeProperty
-> EksVolumeProperty -> EksVolumeProperty
set PropertyType "HostPath" EksVolumeProperty
newValue EksVolumeProperty {Maybe EksEmptyDirProperty
Maybe EksHostPathProperty
Maybe EksPersistentVolumeClaimProperty
Maybe EksSecretProperty
()
Value Text
haddock_workaround_ :: EksVolumeProperty -> ()
emptyDir :: EksVolumeProperty -> Maybe EksEmptyDirProperty
hostPath :: EksVolumeProperty -> Maybe EksHostPathProperty
name :: EksVolumeProperty -> Value Text
persistentVolumeClaim :: EksVolumeProperty -> Maybe EksPersistentVolumeClaimProperty
secret :: EksVolumeProperty -> Maybe EksSecretProperty
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
..}
= EksVolumeProperty {hostPath :: Maybe EksHostPathProperty
hostPath = EksHostPathProperty -> Maybe EksHostPathProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "HostPath" EksVolumeProperty
EksHostPathProperty
newValue, Maybe EksEmptyDirProperty
Maybe EksPersistentVolumeClaimProperty
Maybe EksSecretProperty
()
Value Text
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
..}
instance Property "Name" EksVolumeProperty where
type PropertyType "Name" EksVolumeProperty = Value Prelude.Text
set :: PropertyType "Name" EksVolumeProperty
-> EksVolumeProperty -> EksVolumeProperty
set PropertyType "Name" EksVolumeProperty
newValue EksVolumeProperty {Maybe EksEmptyDirProperty
Maybe EksHostPathProperty
Maybe EksPersistentVolumeClaimProperty
Maybe EksSecretProperty
()
Value Text
haddock_workaround_ :: EksVolumeProperty -> ()
emptyDir :: EksVolumeProperty -> Maybe EksEmptyDirProperty
hostPath :: EksVolumeProperty -> Maybe EksHostPathProperty
name :: EksVolumeProperty -> Value Text
persistentVolumeClaim :: EksVolumeProperty -> Maybe EksPersistentVolumeClaimProperty
secret :: EksVolumeProperty -> Maybe EksSecretProperty
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
..}
= EksVolumeProperty {name :: Value Text
name = PropertyType "Name" EksVolumeProperty
Value Text
newValue, Maybe EksEmptyDirProperty
Maybe EksHostPathProperty
Maybe EksPersistentVolumeClaimProperty
Maybe EksSecretProperty
()
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
..}
instance Property "PersistentVolumeClaim" EksVolumeProperty where
type PropertyType "PersistentVolumeClaim" EksVolumeProperty = EksPersistentVolumeClaimProperty
set :: PropertyType "PersistentVolumeClaim" EksVolumeProperty
-> EksVolumeProperty -> EksVolumeProperty
set PropertyType "PersistentVolumeClaim" EksVolumeProperty
newValue EksVolumeProperty {Maybe EksEmptyDirProperty
Maybe EksHostPathProperty
Maybe EksPersistentVolumeClaimProperty
Maybe EksSecretProperty
()
Value Text
haddock_workaround_ :: EksVolumeProperty -> ()
emptyDir :: EksVolumeProperty -> Maybe EksEmptyDirProperty
hostPath :: EksVolumeProperty -> Maybe EksHostPathProperty
name :: EksVolumeProperty -> Value Text
persistentVolumeClaim :: EksVolumeProperty -> Maybe EksPersistentVolumeClaimProperty
secret :: EksVolumeProperty -> Maybe EksSecretProperty
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
..}
= EksVolumeProperty
{persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
persistentVolumeClaim = EksPersistentVolumeClaimProperty
-> Maybe EksPersistentVolumeClaimProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PersistentVolumeClaim" EksVolumeProperty
EksPersistentVolumeClaimProperty
newValue, Maybe EksEmptyDirProperty
Maybe EksHostPathProperty
Maybe EksSecretProperty
()
Value Text
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
name :: Value Text
secret :: Maybe EksSecretProperty
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
name :: Value Text
secret :: Maybe EksSecretProperty
..}
instance Property "Secret" EksVolumeProperty where
type PropertyType "Secret" EksVolumeProperty = EksSecretProperty
set :: PropertyType "Secret" EksVolumeProperty
-> EksVolumeProperty -> EksVolumeProperty
set PropertyType "Secret" EksVolumeProperty
newValue EksVolumeProperty {Maybe EksEmptyDirProperty
Maybe EksHostPathProperty
Maybe EksPersistentVolumeClaimProperty
Maybe EksSecretProperty
()
Value Text
haddock_workaround_ :: EksVolumeProperty -> ()
emptyDir :: EksVolumeProperty -> Maybe EksEmptyDirProperty
hostPath :: EksVolumeProperty -> Maybe EksHostPathProperty
name :: EksVolumeProperty -> Value Text
persistentVolumeClaim :: EksVolumeProperty -> Maybe EksPersistentVolumeClaimProperty
secret :: EksVolumeProperty -> Maybe EksSecretProperty
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
secret :: Maybe EksSecretProperty
..}
= EksVolumeProperty {secret :: Maybe EksSecretProperty
secret = EksSecretProperty -> Maybe EksSecretProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Secret" EksVolumeProperty
EksSecretProperty
newValue, Maybe EksEmptyDirProperty
Maybe EksHostPathProperty
Maybe EksPersistentVolumeClaimProperty
()
Value Text
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
haddock_workaround_ :: ()
emptyDir :: Maybe EksEmptyDirProperty
hostPath :: Maybe EksHostPathProperty
name :: Value Text
persistentVolumeClaim :: Maybe EksPersistentVolumeClaimProperty
..}