module Stratosphere.Greengrass.ResourceDefinitionVersion.ResourceInstanceProperty (
module Exports, ResourceInstanceProperty(..),
mkResourceInstanceProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Greengrass.ResourceDefinitionVersion.ResourceDataContainerProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ResourceInstanceProperty
=
ResourceInstanceProperty {ResourceInstanceProperty -> ()
haddock_workaround_ :: (),
ResourceInstanceProperty -> Value Text
id :: (Value Prelude.Text),
ResourceInstanceProperty -> Value Text
name :: (Value Prelude.Text),
ResourceInstanceProperty -> ResourceDataContainerProperty
resourceDataContainer :: ResourceDataContainerProperty}
deriving stock (ResourceInstanceProperty -> ResourceInstanceProperty -> Bool
(ResourceInstanceProperty -> ResourceInstanceProperty -> Bool)
-> (ResourceInstanceProperty -> ResourceInstanceProperty -> Bool)
-> Eq ResourceInstanceProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResourceInstanceProperty -> ResourceInstanceProperty -> Bool
== :: ResourceInstanceProperty -> ResourceInstanceProperty -> Bool
$c/= :: ResourceInstanceProperty -> ResourceInstanceProperty -> Bool
/= :: ResourceInstanceProperty -> ResourceInstanceProperty -> Bool
Prelude.Eq, Int -> ResourceInstanceProperty -> ShowS
[ResourceInstanceProperty] -> ShowS
ResourceInstanceProperty -> String
(Int -> ResourceInstanceProperty -> ShowS)
-> (ResourceInstanceProperty -> String)
-> ([ResourceInstanceProperty] -> ShowS)
-> Show ResourceInstanceProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResourceInstanceProperty -> ShowS
showsPrec :: Int -> ResourceInstanceProperty -> ShowS
$cshow :: ResourceInstanceProperty -> String
show :: ResourceInstanceProperty -> String
$cshowList :: [ResourceInstanceProperty] -> ShowS
showList :: [ResourceInstanceProperty] -> ShowS
Prelude.Show)
mkResourceInstanceProperty ::
Value Prelude.Text
-> Value Prelude.Text
-> ResourceDataContainerProperty -> ResourceInstanceProperty
mkResourceInstanceProperty :: Value Text
-> Value Text
-> ResourceDataContainerProperty
-> ResourceInstanceProperty
mkResourceInstanceProperty Value Text
id Value Text
name ResourceDataContainerProperty
resourceDataContainer
= ResourceInstanceProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), id :: Value Text
id = Value Text
id, name :: Value Text
name = Value Text
name,
resourceDataContainer :: ResourceDataContainerProperty
resourceDataContainer = ResourceDataContainerProperty
resourceDataContainer}
instance ToResourceProperties ResourceInstanceProperty where
toResourceProperties :: ResourceInstanceProperty -> ResourceProperties
toResourceProperties ResourceInstanceProperty {()
Value Text
ResourceDataContainerProperty
haddock_workaround_ :: ResourceInstanceProperty -> ()
id :: ResourceInstanceProperty -> Value Text
name :: ResourceInstanceProperty -> Value Text
resourceDataContainer :: ResourceInstanceProperty -> ResourceDataContainerProperty
haddock_workaround_ :: ()
id :: Value Text
name :: Value Text
resourceDataContainer :: ResourceDataContainerProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Greengrass::ResourceDefinitionVersion.ResourceInstance",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Id" 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
id, 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,
Key
"ResourceDataContainer" Key -> ResourceDataContainerProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ResourceDataContainerProperty
resourceDataContainer]}
instance JSON.ToJSON ResourceInstanceProperty where
toJSON :: ResourceInstanceProperty -> Value
toJSON ResourceInstanceProperty {()
Value Text
ResourceDataContainerProperty
haddock_workaround_ :: ResourceInstanceProperty -> ()
id :: ResourceInstanceProperty -> Value Text
name :: ResourceInstanceProperty -> Value Text
resourceDataContainer :: ResourceInstanceProperty -> ResourceDataContainerProperty
haddock_workaround_ :: ()
id :: Value Text
name :: Value Text
resourceDataContainer :: ResourceDataContainerProperty
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"Id" 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
id, 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,
Key
"ResourceDataContainer" Key -> ResourceDataContainerProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ResourceDataContainerProperty
resourceDataContainer]
instance Property "Id" ResourceInstanceProperty where
type PropertyType "Id" ResourceInstanceProperty = Value Prelude.Text
set :: PropertyType "Id" ResourceInstanceProperty
-> ResourceInstanceProperty -> ResourceInstanceProperty
set PropertyType "Id" ResourceInstanceProperty
newValue ResourceInstanceProperty {()
Value Text
ResourceDataContainerProperty
haddock_workaround_ :: ResourceInstanceProperty -> ()
id :: ResourceInstanceProperty -> Value Text
name :: ResourceInstanceProperty -> Value Text
resourceDataContainer :: ResourceInstanceProperty -> ResourceDataContainerProperty
haddock_workaround_ :: ()
id :: Value Text
name :: Value Text
resourceDataContainer :: ResourceDataContainerProperty
..}
= ResourceInstanceProperty {id :: Value Text
id = PropertyType "Id" ResourceInstanceProperty
Value Text
newValue, ()
Value Text
ResourceDataContainerProperty
haddock_workaround_ :: ()
name :: Value Text
resourceDataContainer :: ResourceDataContainerProperty
haddock_workaround_ :: ()
name :: Value Text
resourceDataContainer :: ResourceDataContainerProperty
..}
instance Property "Name" ResourceInstanceProperty where
type PropertyType "Name" ResourceInstanceProperty = Value Prelude.Text
set :: PropertyType "Name" ResourceInstanceProperty
-> ResourceInstanceProperty -> ResourceInstanceProperty
set PropertyType "Name" ResourceInstanceProperty
newValue ResourceInstanceProperty {()
Value Text
ResourceDataContainerProperty
haddock_workaround_ :: ResourceInstanceProperty -> ()
id :: ResourceInstanceProperty -> Value Text
name :: ResourceInstanceProperty -> Value Text
resourceDataContainer :: ResourceInstanceProperty -> ResourceDataContainerProperty
haddock_workaround_ :: ()
id :: Value Text
name :: Value Text
resourceDataContainer :: ResourceDataContainerProperty
..}
= ResourceInstanceProperty {name :: Value Text
name = PropertyType "Name" ResourceInstanceProperty
Value Text
newValue, ()
Value Text
ResourceDataContainerProperty
haddock_workaround_ :: ()
id :: Value Text
resourceDataContainer :: ResourceDataContainerProperty
haddock_workaround_ :: ()
id :: Value Text
resourceDataContainer :: ResourceDataContainerProperty
..}
instance Property "ResourceDataContainer" ResourceInstanceProperty where
type PropertyType "ResourceDataContainer" ResourceInstanceProperty = ResourceDataContainerProperty
set :: PropertyType "ResourceDataContainer" ResourceInstanceProperty
-> ResourceInstanceProperty -> ResourceInstanceProperty
set PropertyType "ResourceDataContainer" ResourceInstanceProperty
newValue ResourceInstanceProperty {()
Value Text
ResourceDataContainerProperty
haddock_workaround_ :: ResourceInstanceProperty -> ()
id :: ResourceInstanceProperty -> Value Text
name :: ResourceInstanceProperty -> Value Text
resourceDataContainer :: ResourceInstanceProperty -> ResourceDataContainerProperty
haddock_workaround_ :: ()
id :: Value Text
name :: Value Text
resourceDataContainer :: ResourceDataContainerProperty
..}
= ResourceInstanceProperty {resourceDataContainer :: ResourceDataContainerProperty
resourceDataContainer = PropertyType "ResourceDataContainer" ResourceInstanceProperty
ResourceDataContainerProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
id :: Value Text
name :: Value Text
haddock_workaround_ :: ()
id :: Value Text
name :: Value Text
..}