module Stratosphere.EC2.SpotFleet.TargetGroupProperty (
TargetGroupProperty(..), mkTargetGroupProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data TargetGroupProperty
=
TargetGroupProperty {TargetGroupProperty -> ()
haddock_workaround_ :: (),
TargetGroupProperty -> Value Text
arn :: (Value Prelude.Text)}
deriving stock (TargetGroupProperty -> TargetGroupProperty -> Bool
(TargetGroupProperty -> TargetGroupProperty -> Bool)
-> (TargetGroupProperty -> TargetGroupProperty -> Bool)
-> Eq TargetGroupProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TargetGroupProperty -> TargetGroupProperty -> Bool
== :: TargetGroupProperty -> TargetGroupProperty -> Bool
$c/= :: TargetGroupProperty -> TargetGroupProperty -> Bool
/= :: TargetGroupProperty -> TargetGroupProperty -> Bool
Prelude.Eq, Int -> TargetGroupProperty -> ShowS
[TargetGroupProperty] -> ShowS
TargetGroupProperty -> String
(Int -> TargetGroupProperty -> ShowS)
-> (TargetGroupProperty -> String)
-> ([TargetGroupProperty] -> ShowS)
-> Show TargetGroupProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TargetGroupProperty -> ShowS
showsPrec :: Int -> TargetGroupProperty -> ShowS
$cshow :: TargetGroupProperty -> String
show :: TargetGroupProperty -> String
$cshowList :: [TargetGroupProperty] -> ShowS
showList :: [TargetGroupProperty] -> ShowS
Prelude.Show)
mkTargetGroupProperty :: Value Prelude.Text -> TargetGroupProperty
mkTargetGroupProperty :: Value Text -> TargetGroupProperty
mkTargetGroupProperty Value Text
arn
= TargetGroupProperty {haddock_workaround_ :: ()
haddock_workaround_ = (), arn :: Value Text
arn = Value Text
arn}
instance ToResourceProperties TargetGroupProperty where
toResourceProperties :: TargetGroupProperty -> ResourceProperties
toResourceProperties TargetGroupProperty {()
Value Text
haddock_workaround_ :: TargetGroupProperty -> ()
arn :: TargetGroupProperty -> Value Text
haddock_workaround_ :: ()
arn :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::EC2::SpotFleet.TargetGroup",
supportsTags :: Bool
supportsTags = Bool
Prelude.False, properties :: Object
properties = [Key
"Arn" 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
arn]}
instance JSON.ToJSON TargetGroupProperty where
toJSON :: TargetGroupProperty -> Value
toJSON TargetGroupProperty {()
Value Text
haddock_workaround_ :: TargetGroupProperty -> ()
arn :: TargetGroupProperty -> Value Text
haddock_workaround_ :: ()
arn :: Value Text
..} = [(Key, Value)] -> Value
JSON.object [Key
"Arn" 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
arn]
instance Property "Arn" TargetGroupProperty where
type PropertyType "Arn" TargetGroupProperty = Value Prelude.Text
set :: PropertyType "Arn" TargetGroupProperty
-> TargetGroupProperty -> TargetGroupProperty
set PropertyType "Arn" TargetGroupProperty
newValue TargetGroupProperty {()
Value Text
haddock_workaround_ :: TargetGroupProperty -> ()
arn :: TargetGroupProperty -> Value Text
haddock_workaround_ :: ()
arn :: Value Text
..}
= TargetGroupProperty {arn :: Value Text
arn = PropertyType "Arn" TargetGroupProperty
Value Text
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}