module Stratosphere.SSMContacts.Plan.ContactTargetInfoProperty (
ContactTargetInfoProperty(..), mkContactTargetInfoProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ContactTargetInfoProperty
=
ContactTargetInfoProperty {ContactTargetInfoProperty -> ()
haddock_workaround_ :: (),
ContactTargetInfoProperty -> Value Text
contactId :: (Value Prelude.Text),
ContactTargetInfoProperty -> Value Bool
isEssential :: (Value Prelude.Bool)}
deriving stock (ContactTargetInfoProperty -> ContactTargetInfoProperty -> Bool
(ContactTargetInfoProperty -> ContactTargetInfoProperty -> Bool)
-> (ContactTargetInfoProperty -> ContactTargetInfoProperty -> Bool)
-> Eq ContactTargetInfoProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ContactTargetInfoProperty -> ContactTargetInfoProperty -> Bool
== :: ContactTargetInfoProperty -> ContactTargetInfoProperty -> Bool
$c/= :: ContactTargetInfoProperty -> ContactTargetInfoProperty -> Bool
/= :: ContactTargetInfoProperty -> ContactTargetInfoProperty -> Bool
Prelude.Eq, Int -> ContactTargetInfoProperty -> ShowS
[ContactTargetInfoProperty] -> ShowS
ContactTargetInfoProperty -> String
(Int -> ContactTargetInfoProperty -> ShowS)
-> (ContactTargetInfoProperty -> String)
-> ([ContactTargetInfoProperty] -> ShowS)
-> Show ContactTargetInfoProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ContactTargetInfoProperty -> ShowS
showsPrec :: Int -> ContactTargetInfoProperty -> ShowS
$cshow :: ContactTargetInfoProperty -> String
show :: ContactTargetInfoProperty -> String
$cshowList :: [ContactTargetInfoProperty] -> ShowS
showList :: [ContactTargetInfoProperty] -> ShowS
Prelude.Show)
mkContactTargetInfoProperty ::
Value Prelude.Text
-> Value Prelude.Bool -> ContactTargetInfoProperty
mkContactTargetInfoProperty :: Value Text -> Value Bool -> ContactTargetInfoProperty
mkContactTargetInfoProperty Value Text
contactId Value Bool
isEssential
= ContactTargetInfoProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), contactId :: Value Text
contactId = Value Text
contactId,
isEssential :: Value Bool
isEssential = Value Bool
isEssential}
instance ToResourceProperties ContactTargetInfoProperty where
toResourceProperties :: ContactTargetInfoProperty -> ResourceProperties
toResourceProperties ContactTargetInfoProperty {()
Value Bool
Value Text
haddock_workaround_ :: ContactTargetInfoProperty -> ()
contactId :: ContactTargetInfoProperty -> Value Text
isEssential :: ContactTargetInfoProperty -> Value Bool
haddock_workaround_ :: ()
contactId :: Value Text
isEssential :: Value Bool
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::SSMContacts::Plan.ContactTargetInfo",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"ContactId" 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
contactId,
Key
"IsEssential" Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Bool
isEssential]}
instance JSON.ToJSON ContactTargetInfoProperty where
toJSON :: ContactTargetInfoProperty -> Value
toJSON ContactTargetInfoProperty {()
Value Bool
Value Text
haddock_workaround_ :: ContactTargetInfoProperty -> ()
contactId :: ContactTargetInfoProperty -> Value Text
isEssential :: ContactTargetInfoProperty -> Value Bool
haddock_workaround_ :: ()
contactId :: Value Text
isEssential :: Value Bool
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"ContactId" 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
contactId, Key
"IsEssential" Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Bool
isEssential]
instance Property "ContactId" ContactTargetInfoProperty where
type PropertyType "ContactId" ContactTargetInfoProperty = Value Prelude.Text
set :: PropertyType "ContactId" ContactTargetInfoProperty
-> ContactTargetInfoProperty -> ContactTargetInfoProperty
set PropertyType "ContactId" ContactTargetInfoProperty
newValue ContactTargetInfoProperty {()
Value Bool
Value Text
haddock_workaround_ :: ContactTargetInfoProperty -> ()
contactId :: ContactTargetInfoProperty -> Value Text
isEssential :: ContactTargetInfoProperty -> Value Bool
haddock_workaround_ :: ()
contactId :: Value Text
isEssential :: Value Bool
..}
= ContactTargetInfoProperty {contactId :: Value Text
contactId = PropertyType "ContactId" ContactTargetInfoProperty
Value Text
newValue, ()
Value Bool
haddock_workaround_ :: ()
isEssential :: Value Bool
haddock_workaround_ :: ()
isEssential :: Value Bool
..}
instance Property "IsEssential" ContactTargetInfoProperty where
type PropertyType "IsEssential" ContactTargetInfoProperty = Value Prelude.Bool
set :: PropertyType "IsEssential" ContactTargetInfoProperty
-> ContactTargetInfoProperty -> ContactTargetInfoProperty
set PropertyType "IsEssential" ContactTargetInfoProperty
newValue ContactTargetInfoProperty {()
Value Bool
Value Text
haddock_workaround_ :: ContactTargetInfoProperty -> ()
contactId :: ContactTargetInfoProperty -> Value Text
isEssential :: ContactTargetInfoProperty -> Value Bool
haddock_workaround_ :: ()
contactId :: Value Text
isEssential :: Value Bool
..}
= ContactTargetInfoProperty {isEssential :: Value Bool
isEssential = PropertyType "IsEssential" ContactTargetInfoProperty
Value Bool
newValue, ()
Value Text
haddock_workaround_ :: ()
contactId :: Value Text
haddock_workaround_ :: ()
contactId :: Value Text
..}