module Stratosphere.EC2.Host (
Host(..), mkHost
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data Host
=
Host {Host -> ()
haddock_workaround_ :: (),
Host -> Maybe (Value Text)
assetId :: (Prelude.Maybe (Value Prelude.Text)),
Host -> Maybe (Value Text)
autoPlacement :: (Prelude.Maybe (Value Prelude.Text)),
Host -> Value Text
availabilityZone :: (Value Prelude.Text),
Host -> Maybe (Value Text)
hostMaintenance :: (Prelude.Maybe (Value Prelude.Text)),
Host -> Maybe (Value Text)
hostRecovery :: (Prelude.Maybe (Value Prelude.Text)),
Host -> Maybe (Value Text)
instanceFamily :: (Prelude.Maybe (Value Prelude.Text)),
Host -> Maybe (Value Text)
instanceType :: (Prelude.Maybe (Value Prelude.Text)),
Host -> Maybe (Value Text)
outpostArn :: (Prelude.Maybe (Value Prelude.Text)),
Host -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag])}
deriving stock (Host -> Host -> Bool
(Host -> Host -> Bool) -> (Host -> Host -> Bool) -> Eq Host
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Host -> Host -> Bool
== :: Host -> Host -> Bool
$c/= :: Host -> Host -> Bool
/= :: Host -> Host -> Bool
Prelude.Eq, Int -> Host -> ShowS
[Host] -> ShowS
Host -> String
(Int -> Host -> ShowS)
-> (Host -> String) -> ([Host] -> ShowS) -> Show Host
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Host -> ShowS
showsPrec :: Int -> Host -> ShowS
$cshow :: Host -> String
show :: Host -> String
$cshowList :: [Host] -> ShowS
showList :: [Host] -> ShowS
Prelude.Show)
mkHost :: Value Prelude.Text -> Host
mkHost :: Value Text -> Host
mkHost Value Text
availabilityZone
= Host
{haddock_workaround_ :: ()
haddock_workaround_ = (), availabilityZone :: Value Text
availabilityZone = Value Text
availabilityZone,
assetId :: Maybe (Value Text)
assetId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, autoPlacement :: Maybe (Value Text)
autoPlacement = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
hostMaintenance :: Maybe (Value Text)
hostMaintenance = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, hostRecovery :: Maybe (Value Text)
hostRecovery = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
instanceFamily :: Maybe (Value Text)
instanceFamily = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, instanceType :: Maybe (Value Text)
instanceType = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
outpostArn :: Maybe (Value Text)
outpostArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties Host where
toResourceProperties :: Host -> ResourceProperties
toResourceProperties Host {Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Host -> ()
assetId :: Host -> Maybe (Value Text)
autoPlacement :: Host -> Maybe (Value Text)
availabilityZone :: Host -> Value Text
hostMaintenance :: Host -> Maybe (Value Text)
hostRecovery :: Host -> Maybe (Value Text)
instanceFamily :: Host -> Maybe (Value Text)
instanceType :: Host -> Maybe (Value Text)
outpostArn :: Host -> Maybe (Value Text)
tags :: Host -> Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::EC2::Host", supportsTags :: Bool
supportsTags = Bool
Prelude.True,
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
"AvailabilityZone" 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
availabilityZone]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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..=) Key
"AssetId" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
assetId,
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..=) Key
"AutoPlacement" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
autoPlacement,
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..=) Key
"HostMaintenance" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
hostMaintenance,
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..=) Key
"HostRecovery" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
hostRecovery,
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..=) Key
"InstanceFamily" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
instanceFamily,
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..=) Key
"InstanceType" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
instanceType,
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..=) Key
"OutpostArn" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
outpostArn,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags]))}
instance JSON.ToJSON Host where
toJSON :: Host -> Value
toJSON Host {Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Host -> ()
assetId :: Host -> Maybe (Value Text)
autoPlacement :: Host -> Maybe (Value Text)
availabilityZone :: Host -> Value Text
hostMaintenance :: Host -> Maybe (Value Text)
hostRecovery :: Host -> Maybe (Value Text)
instanceFamily :: Host -> Maybe (Value Text)
instanceType :: Host -> Maybe (Value Text)
outpostArn :: Host -> Maybe (Value Text)
tags :: Host -> Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
= [(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
"AvailabilityZone" 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
availabilityZone]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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..=) Key
"AssetId" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
assetId,
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..=) Key
"AutoPlacement" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
autoPlacement,
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..=) Key
"HostMaintenance" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
hostMaintenance,
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..=) Key
"HostRecovery" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
hostRecovery,
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..=) Key
"InstanceFamily" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
instanceFamily,
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..=) Key
"InstanceType" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
instanceType,
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..=) Key
"OutpostArn" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
outpostArn,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags])))
instance Property "AssetId" Host where
type PropertyType "AssetId" Host = Value Prelude.Text
set :: PropertyType "AssetId" Host -> Host -> Host
set PropertyType "AssetId" Host
newValue Host {Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Host -> ()
assetId :: Host -> Maybe (Value Text)
autoPlacement :: Host -> Maybe (Value Text)
availabilityZone :: Host -> Value Text
hostMaintenance :: Host -> Maybe (Value Text)
hostRecovery :: Host -> Maybe (Value Text)
instanceFamily :: Host -> Maybe (Value Text)
instanceType :: Host -> Maybe (Value Text)
outpostArn :: Host -> Maybe (Value Text)
tags :: Host -> Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..} = Host {assetId :: Maybe (Value Text)
assetId = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AssetId" Host
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
haddock_workaround_ :: ()
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
instance Property "AutoPlacement" Host where
type PropertyType "AutoPlacement" Host = Value Prelude.Text
set :: PropertyType "AutoPlacement" Host -> Host -> Host
set PropertyType "AutoPlacement" Host
newValue Host {Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Host -> ()
assetId :: Host -> Maybe (Value Text)
autoPlacement :: Host -> Maybe (Value Text)
availabilityZone :: Host -> Value Text
hostMaintenance :: Host -> Maybe (Value Text)
hostRecovery :: Host -> Maybe (Value Text)
instanceFamily :: Host -> Maybe (Value Text)
instanceType :: Host -> Maybe (Value Text)
outpostArn :: Host -> Maybe (Value Text)
tags :: Host -> Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
= Host {autoPlacement :: Maybe (Value Text)
autoPlacement = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AutoPlacement" Host
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
instance Property "AvailabilityZone" Host where
type PropertyType "AvailabilityZone" Host = Value Prelude.Text
set :: PropertyType "AvailabilityZone" Host -> Host -> Host
set PropertyType "AvailabilityZone" Host
newValue Host {Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Host -> ()
assetId :: Host -> Maybe (Value Text)
autoPlacement :: Host -> Maybe (Value Text)
availabilityZone :: Host -> Value Text
hostMaintenance :: Host -> Maybe (Value Text)
hostRecovery :: Host -> Maybe (Value Text)
instanceFamily :: Host -> Maybe (Value Text)
instanceType :: Host -> Maybe (Value Text)
outpostArn :: Host -> Maybe (Value Text)
tags :: Host -> Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..} = Host {availabilityZone :: Value Text
availabilityZone = PropertyType "AvailabilityZone" Host
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
()
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
instance Property "HostMaintenance" Host where
type PropertyType "HostMaintenance" Host = Value Prelude.Text
set :: PropertyType "HostMaintenance" Host -> Host -> Host
set PropertyType "HostMaintenance" Host
newValue Host {Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Host -> ()
assetId :: Host -> Maybe (Value Text)
autoPlacement :: Host -> Maybe (Value Text)
availabilityZone :: Host -> Value Text
hostMaintenance :: Host -> Maybe (Value Text)
hostRecovery :: Host -> Maybe (Value Text)
instanceFamily :: Host -> Maybe (Value Text)
instanceType :: Host -> Maybe (Value Text)
outpostArn :: Host -> Maybe (Value Text)
tags :: Host -> Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
= Host {hostMaintenance :: Maybe (Value Text)
hostMaintenance = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "HostMaintenance" Host
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
instance Property "HostRecovery" Host where
type PropertyType "HostRecovery" Host = Value Prelude.Text
set :: PropertyType "HostRecovery" Host -> Host -> Host
set PropertyType "HostRecovery" Host
newValue Host {Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Host -> ()
assetId :: Host -> Maybe (Value Text)
autoPlacement :: Host -> Maybe (Value Text)
availabilityZone :: Host -> Value Text
hostMaintenance :: Host -> Maybe (Value Text)
hostRecovery :: Host -> Maybe (Value Text)
instanceFamily :: Host -> Maybe (Value Text)
instanceType :: Host -> Maybe (Value Text)
outpostArn :: Host -> Maybe (Value Text)
tags :: Host -> Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
= Host {hostRecovery :: Maybe (Value Text)
hostRecovery = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "HostRecovery" Host
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
instance Property "InstanceFamily" Host where
type PropertyType "InstanceFamily" Host = Value Prelude.Text
set :: PropertyType "InstanceFamily" Host -> Host -> Host
set PropertyType "InstanceFamily" Host
newValue Host {Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Host -> ()
assetId :: Host -> Maybe (Value Text)
autoPlacement :: Host -> Maybe (Value Text)
availabilityZone :: Host -> Value Text
hostMaintenance :: Host -> Maybe (Value Text)
hostRecovery :: Host -> Maybe (Value Text)
instanceFamily :: Host -> Maybe (Value Text)
instanceType :: Host -> Maybe (Value Text)
outpostArn :: Host -> Maybe (Value Text)
tags :: Host -> Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
= Host {instanceFamily :: Maybe (Value Text)
instanceFamily = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InstanceFamily" Host
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
instance Property "InstanceType" Host where
type PropertyType "InstanceType" Host = Value Prelude.Text
set :: PropertyType "InstanceType" Host -> Host -> Host
set PropertyType "InstanceType" Host
newValue Host {Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Host -> ()
assetId :: Host -> Maybe (Value Text)
autoPlacement :: Host -> Maybe (Value Text)
availabilityZone :: Host -> Value Text
hostMaintenance :: Host -> Maybe (Value Text)
hostRecovery :: Host -> Maybe (Value Text)
instanceFamily :: Host -> Maybe (Value Text)
instanceType :: Host -> Maybe (Value Text)
outpostArn :: Host -> Maybe (Value Text)
tags :: Host -> Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
= Host {instanceType :: Maybe (Value Text)
instanceType = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InstanceType" Host
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
instance Property "OutpostArn" Host where
type PropertyType "OutpostArn" Host = Value Prelude.Text
set :: PropertyType "OutpostArn" Host -> Host -> Host
set PropertyType "OutpostArn" Host
newValue Host {Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Host -> ()
assetId :: Host -> Maybe (Value Text)
autoPlacement :: Host -> Maybe (Value Text)
availabilityZone :: Host -> Value Text
hostMaintenance :: Host -> Maybe (Value Text)
hostRecovery :: Host -> Maybe (Value Text)
instanceFamily :: Host -> Maybe (Value Text)
instanceType :: Host -> Maybe (Value Text)
outpostArn :: Host -> Maybe (Value Text)
tags :: Host -> Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
= Host {outpostArn :: Maybe (Value Text)
outpostArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "OutpostArn" Host
Value Text
newValue, Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
tags :: Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
tags :: Maybe [Tag]
..}
instance Property "Tags" Host where
type PropertyType "Tags" Host = [Tag]
set :: PropertyType "Tags" Host -> Host -> Host
set PropertyType "Tags" Host
newValue Host {Maybe [Tag]
Maybe (Value Text)
()
Value Text
haddock_workaround_ :: Host -> ()
assetId :: Host -> Maybe (Value Text)
autoPlacement :: Host -> Maybe (Value Text)
availabilityZone :: Host -> Value Text
hostMaintenance :: Host -> Maybe (Value Text)
hostRecovery :: Host -> Maybe (Value Text)
instanceFamily :: Host -> Maybe (Value Text)
instanceType :: Host -> Maybe (Value Text)
outpostArn :: Host -> Maybe (Value Text)
tags :: Host -> Maybe [Tag]
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
tags :: Maybe [Tag]
..} = Host {tags :: Maybe [Tag]
tags = [Tag] -> Maybe [Tag]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [Tag]
PropertyType "Tags" Host
newValue, Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
haddock_workaround_ :: ()
assetId :: Maybe (Value Text)
autoPlacement :: Maybe (Value Text)
availabilityZone :: Value Text
hostMaintenance :: Maybe (Value Text)
hostRecovery :: Maybe (Value Text)
instanceFamily :: Maybe (Value Text)
instanceType :: Maybe (Value Text)
outpostArn :: Maybe (Value Text)
..}