module Stratosphere.Connect.TaskTemplate.InvisibleFieldInfoProperty (
module Exports, InvisibleFieldInfoProperty(..),
mkInvisibleFieldInfoProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Connect.TaskTemplate.FieldIdentifierProperty as Exports
import Stratosphere.ResourceProperties
data InvisibleFieldInfoProperty
=
InvisibleFieldInfoProperty {InvisibleFieldInfoProperty -> ()
haddock_workaround_ :: (),
InvisibleFieldInfoProperty -> FieldIdentifierProperty
id :: FieldIdentifierProperty}
deriving stock (InvisibleFieldInfoProperty -> InvisibleFieldInfoProperty -> Bool
(InvisibleFieldInfoProperty -> InvisibleFieldInfoProperty -> Bool)
-> (InvisibleFieldInfoProperty
-> InvisibleFieldInfoProperty -> Bool)
-> Eq InvisibleFieldInfoProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InvisibleFieldInfoProperty -> InvisibleFieldInfoProperty -> Bool
== :: InvisibleFieldInfoProperty -> InvisibleFieldInfoProperty -> Bool
$c/= :: InvisibleFieldInfoProperty -> InvisibleFieldInfoProperty -> Bool
/= :: InvisibleFieldInfoProperty -> InvisibleFieldInfoProperty -> Bool
Prelude.Eq, Int -> InvisibleFieldInfoProperty -> ShowS
[InvisibleFieldInfoProperty] -> ShowS
InvisibleFieldInfoProperty -> String
(Int -> InvisibleFieldInfoProperty -> ShowS)
-> (InvisibleFieldInfoProperty -> String)
-> ([InvisibleFieldInfoProperty] -> ShowS)
-> Show InvisibleFieldInfoProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InvisibleFieldInfoProperty -> ShowS
showsPrec :: Int -> InvisibleFieldInfoProperty -> ShowS
$cshow :: InvisibleFieldInfoProperty -> String
show :: InvisibleFieldInfoProperty -> String
$cshowList :: [InvisibleFieldInfoProperty] -> ShowS
showList :: [InvisibleFieldInfoProperty] -> ShowS
Prelude.Show)
mkInvisibleFieldInfoProperty ::
FieldIdentifierProperty -> InvisibleFieldInfoProperty
mkInvisibleFieldInfoProperty :: FieldIdentifierProperty -> InvisibleFieldInfoProperty
mkInvisibleFieldInfoProperty FieldIdentifierProperty
id
= InvisibleFieldInfoProperty {haddock_workaround_ :: ()
haddock_workaround_ = (), id :: FieldIdentifierProperty
id = FieldIdentifierProperty
id}
instance ToResourceProperties InvisibleFieldInfoProperty where
toResourceProperties :: InvisibleFieldInfoProperty -> ResourceProperties
toResourceProperties InvisibleFieldInfoProperty {()
FieldIdentifierProperty
haddock_workaround_ :: InvisibleFieldInfoProperty -> ()
id :: InvisibleFieldInfoProperty -> FieldIdentifierProperty
haddock_workaround_ :: ()
id :: FieldIdentifierProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Connect::TaskTemplate.InvisibleFieldInfo",
supportsTags :: Bool
supportsTags = Bool
Prelude.False, properties :: Object
properties = [Key
"Id" Key -> FieldIdentifierProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= FieldIdentifierProperty
id]}
instance JSON.ToJSON InvisibleFieldInfoProperty where
toJSON :: InvisibleFieldInfoProperty -> Value
toJSON InvisibleFieldInfoProperty {()
FieldIdentifierProperty
haddock_workaround_ :: InvisibleFieldInfoProperty -> ()
id :: InvisibleFieldInfoProperty -> FieldIdentifierProperty
haddock_workaround_ :: ()
id :: FieldIdentifierProperty
..}
= [(Key, Value)] -> Value
JSON.object [Key
"Id" Key -> FieldIdentifierProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= FieldIdentifierProperty
id]
instance Property "Id" InvisibleFieldInfoProperty where
type PropertyType "Id" InvisibleFieldInfoProperty = FieldIdentifierProperty
set :: PropertyType "Id" InvisibleFieldInfoProperty
-> InvisibleFieldInfoProperty -> InvisibleFieldInfoProperty
set PropertyType "Id" InvisibleFieldInfoProperty
newValue InvisibleFieldInfoProperty {()
FieldIdentifierProperty
haddock_workaround_ :: InvisibleFieldInfoProperty -> ()
id :: InvisibleFieldInfoProperty -> FieldIdentifierProperty
haddock_workaround_ :: ()
id :: FieldIdentifierProperty
..}
= InvisibleFieldInfoProperty {id :: FieldIdentifierProperty
id = PropertyType "Id" InvisibleFieldInfoProperty
FieldIdentifierProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}