{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.CloudFormation.Types.StackResourceDrift where
import Amazonka.CloudFormation.Types.ModuleInfo
import Amazonka.CloudFormation.Types.PhysicalResourceIdContextKeyValuePair
import Amazonka.CloudFormation.Types.PropertyDifference
import Amazonka.CloudFormation.Types.StackResourceDriftStatus
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
data StackResourceDrift = StackResourceDrift'
{
StackResourceDrift -> Maybe Text
actualProperties :: Prelude.Maybe Prelude.Text,
StackResourceDrift -> Maybe Text
expectedProperties :: Prelude.Maybe Prelude.Text,
StackResourceDrift -> Maybe ModuleInfo
moduleInfo :: Prelude.Maybe ModuleInfo,
StackResourceDrift -> Maybe Text
physicalResourceId :: Prelude.Maybe Prelude.Text,
StackResourceDrift -> Maybe [PhysicalResourceIdContextKeyValuePair]
physicalResourceIdContext :: Prelude.Maybe [PhysicalResourceIdContextKeyValuePair],
StackResourceDrift -> Maybe [PropertyDifference]
propertyDifferences :: Prelude.Maybe [PropertyDifference],
StackResourceDrift -> Text
stackId :: Prelude.Text,
StackResourceDrift -> Text
logicalResourceId :: Prelude.Text,
StackResourceDrift -> Text
resourceType :: Prelude.Text,
StackResourceDrift -> StackResourceDriftStatus
stackResourceDriftStatus :: StackResourceDriftStatus,
StackResourceDrift -> ISO8601
timestamp :: Data.ISO8601
}
deriving (StackResourceDrift -> StackResourceDrift -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StackResourceDrift -> StackResourceDrift -> Bool
$c/= :: StackResourceDrift -> StackResourceDrift -> Bool
== :: StackResourceDrift -> StackResourceDrift -> Bool
$c== :: StackResourceDrift -> StackResourceDrift -> Bool
Prelude.Eq, ReadPrec [StackResourceDrift]
ReadPrec StackResourceDrift
Int -> ReadS StackResourceDrift
ReadS [StackResourceDrift]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StackResourceDrift]
$creadListPrec :: ReadPrec [StackResourceDrift]
readPrec :: ReadPrec StackResourceDrift
$creadPrec :: ReadPrec StackResourceDrift
readList :: ReadS [StackResourceDrift]
$creadList :: ReadS [StackResourceDrift]
readsPrec :: Int -> ReadS StackResourceDrift
$creadsPrec :: Int -> ReadS StackResourceDrift
Prelude.Read, Int -> StackResourceDrift -> ShowS
[StackResourceDrift] -> ShowS
StackResourceDrift -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StackResourceDrift] -> ShowS
$cshowList :: [StackResourceDrift] -> ShowS
show :: StackResourceDrift -> String
$cshow :: StackResourceDrift -> String
showsPrec :: Int -> StackResourceDrift -> ShowS
$cshowsPrec :: Int -> StackResourceDrift -> ShowS
Prelude.Show, forall x. Rep StackResourceDrift x -> StackResourceDrift
forall x. StackResourceDrift -> Rep StackResourceDrift x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StackResourceDrift x -> StackResourceDrift
$cfrom :: forall x. StackResourceDrift -> Rep StackResourceDrift x
Prelude.Generic)
newStackResourceDrift ::
Prelude.Text ->
Prelude.Text ->
Prelude.Text ->
StackResourceDriftStatus ->
Prelude.UTCTime ->
StackResourceDrift
newStackResourceDrift :: Text
-> Text
-> Text
-> StackResourceDriftStatus
-> UTCTime
-> StackResourceDrift
newStackResourceDrift
Text
pStackId_
Text
pLogicalResourceId_
Text
pResourceType_
StackResourceDriftStatus
pStackResourceDriftStatus_
UTCTime
pTimestamp_ =
StackResourceDrift'
{ $sel:actualProperties:StackResourceDrift' :: Maybe Text
actualProperties =
forall a. Maybe a
Prelude.Nothing,
$sel:expectedProperties:StackResourceDrift' :: Maybe Text
expectedProperties = forall a. Maybe a
Prelude.Nothing,
$sel:moduleInfo:StackResourceDrift' :: Maybe ModuleInfo
moduleInfo = forall a. Maybe a
Prelude.Nothing,
$sel:physicalResourceId:StackResourceDrift' :: Maybe Text
physicalResourceId = forall a. Maybe a
Prelude.Nothing,
$sel:physicalResourceIdContext:StackResourceDrift' :: Maybe [PhysicalResourceIdContextKeyValuePair]
physicalResourceIdContext = forall a. Maybe a
Prelude.Nothing,
$sel:propertyDifferences:StackResourceDrift' :: Maybe [PropertyDifference]
propertyDifferences = forall a. Maybe a
Prelude.Nothing,
$sel:stackId:StackResourceDrift' :: Text
stackId = Text
pStackId_,
$sel:logicalResourceId:StackResourceDrift' :: Text
logicalResourceId = Text
pLogicalResourceId_,
$sel:resourceType:StackResourceDrift' :: Text
resourceType = Text
pResourceType_,
$sel:stackResourceDriftStatus:StackResourceDrift' :: StackResourceDriftStatus
stackResourceDriftStatus =
StackResourceDriftStatus
pStackResourceDriftStatus_,
$sel:timestamp:StackResourceDrift' :: ISO8601
timestamp = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pTimestamp_
}
stackResourceDrift_actualProperties :: Lens.Lens' StackResourceDrift (Prelude.Maybe Prelude.Text)
stackResourceDrift_actualProperties :: Lens' StackResourceDrift (Maybe Text)
stackResourceDrift_actualProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackResourceDrift' {Maybe Text
actualProperties :: Maybe Text
$sel:actualProperties:StackResourceDrift' :: StackResourceDrift -> Maybe Text
actualProperties} -> Maybe Text
actualProperties) (\s :: StackResourceDrift
s@StackResourceDrift' {} Maybe Text
a -> StackResourceDrift
s {$sel:actualProperties:StackResourceDrift' :: Maybe Text
actualProperties = Maybe Text
a} :: StackResourceDrift)
stackResourceDrift_expectedProperties :: Lens.Lens' StackResourceDrift (Prelude.Maybe Prelude.Text)
stackResourceDrift_expectedProperties :: Lens' StackResourceDrift (Maybe Text)
stackResourceDrift_expectedProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackResourceDrift' {Maybe Text
expectedProperties :: Maybe Text
$sel:expectedProperties:StackResourceDrift' :: StackResourceDrift -> Maybe Text
expectedProperties} -> Maybe Text
expectedProperties) (\s :: StackResourceDrift
s@StackResourceDrift' {} Maybe Text
a -> StackResourceDrift
s {$sel:expectedProperties:StackResourceDrift' :: Maybe Text
expectedProperties = Maybe Text
a} :: StackResourceDrift)
stackResourceDrift_moduleInfo :: Lens.Lens' StackResourceDrift (Prelude.Maybe ModuleInfo)
stackResourceDrift_moduleInfo :: Lens' StackResourceDrift (Maybe ModuleInfo)
stackResourceDrift_moduleInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackResourceDrift' {Maybe ModuleInfo
moduleInfo :: Maybe ModuleInfo
$sel:moduleInfo:StackResourceDrift' :: StackResourceDrift -> Maybe ModuleInfo
moduleInfo} -> Maybe ModuleInfo
moduleInfo) (\s :: StackResourceDrift
s@StackResourceDrift' {} Maybe ModuleInfo
a -> StackResourceDrift
s {$sel:moduleInfo:StackResourceDrift' :: Maybe ModuleInfo
moduleInfo = Maybe ModuleInfo
a} :: StackResourceDrift)
stackResourceDrift_physicalResourceId :: Lens.Lens' StackResourceDrift (Prelude.Maybe Prelude.Text)
stackResourceDrift_physicalResourceId :: Lens' StackResourceDrift (Maybe Text)
stackResourceDrift_physicalResourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackResourceDrift' {Maybe Text
physicalResourceId :: Maybe Text
$sel:physicalResourceId:StackResourceDrift' :: StackResourceDrift -> Maybe Text
physicalResourceId} -> Maybe Text
physicalResourceId) (\s :: StackResourceDrift
s@StackResourceDrift' {} Maybe Text
a -> StackResourceDrift
s {$sel:physicalResourceId:StackResourceDrift' :: Maybe Text
physicalResourceId = Maybe Text
a} :: StackResourceDrift)
stackResourceDrift_physicalResourceIdContext :: Lens.Lens' StackResourceDrift (Prelude.Maybe [PhysicalResourceIdContextKeyValuePair])
stackResourceDrift_physicalResourceIdContext :: Lens'
StackResourceDrift (Maybe [PhysicalResourceIdContextKeyValuePair])
stackResourceDrift_physicalResourceIdContext = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackResourceDrift' {Maybe [PhysicalResourceIdContextKeyValuePair]
physicalResourceIdContext :: Maybe [PhysicalResourceIdContextKeyValuePair]
$sel:physicalResourceIdContext:StackResourceDrift' :: StackResourceDrift -> Maybe [PhysicalResourceIdContextKeyValuePair]
physicalResourceIdContext} -> Maybe [PhysicalResourceIdContextKeyValuePair]
physicalResourceIdContext) (\s :: StackResourceDrift
s@StackResourceDrift' {} Maybe [PhysicalResourceIdContextKeyValuePair]
a -> StackResourceDrift
s {$sel:physicalResourceIdContext:StackResourceDrift' :: Maybe [PhysicalResourceIdContextKeyValuePair]
physicalResourceIdContext = Maybe [PhysicalResourceIdContextKeyValuePair]
a} :: StackResourceDrift) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
stackResourceDrift_propertyDifferences :: Lens.Lens' StackResourceDrift (Prelude.Maybe [PropertyDifference])
stackResourceDrift_propertyDifferences :: Lens' StackResourceDrift (Maybe [PropertyDifference])
stackResourceDrift_propertyDifferences = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackResourceDrift' {Maybe [PropertyDifference]
propertyDifferences :: Maybe [PropertyDifference]
$sel:propertyDifferences:StackResourceDrift' :: StackResourceDrift -> Maybe [PropertyDifference]
propertyDifferences} -> Maybe [PropertyDifference]
propertyDifferences) (\s :: StackResourceDrift
s@StackResourceDrift' {} Maybe [PropertyDifference]
a -> StackResourceDrift
s {$sel:propertyDifferences:StackResourceDrift' :: Maybe [PropertyDifference]
propertyDifferences = Maybe [PropertyDifference]
a} :: StackResourceDrift) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
stackResourceDrift_stackId :: Lens.Lens' StackResourceDrift Prelude.Text
stackResourceDrift_stackId :: Lens' StackResourceDrift Text
stackResourceDrift_stackId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackResourceDrift' {Text
stackId :: Text
$sel:stackId:StackResourceDrift' :: StackResourceDrift -> Text
stackId} -> Text
stackId) (\s :: StackResourceDrift
s@StackResourceDrift' {} Text
a -> StackResourceDrift
s {$sel:stackId:StackResourceDrift' :: Text
stackId = Text
a} :: StackResourceDrift)
stackResourceDrift_logicalResourceId :: Lens.Lens' StackResourceDrift Prelude.Text
stackResourceDrift_logicalResourceId :: Lens' StackResourceDrift Text
stackResourceDrift_logicalResourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackResourceDrift' {Text
logicalResourceId :: Text
$sel:logicalResourceId:StackResourceDrift' :: StackResourceDrift -> Text
logicalResourceId} -> Text
logicalResourceId) (\s :: StackResourceDrift
s@StackResourceDrift' {} Text
a -> StackResourceDrift
s {$sel:logicalResourceId:StackResourceDrift' :: Text
logicalResourceId = Text
a} :: StackResourceDrift)
stackResourceDrift_resourceType :: Lens.Lens' StackResourceDrift Prelude.Text
stackResourceDrift_resourceType :: Lens' StackResourceDrift Text
stackResourceDrift_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackResourceDrift' {Text
resourceType :: Text
$sel:resourceType:StackResourceDrift' :: StackResourceDrift -> Text
resourceType} -> Text
resourceType) (\s :: StackResourceDrift
s@StackResourceDrift' {} Text
a -> StackResourceDrift
s {$sel:resourceType:StackResourceDrift' :: Text
resourceType = Text
a} :: StackResourceDrift)
stackResourceDrift_stackResourceDriftStatus :: Lens.Lens' StackResourceDrift StackResourceDriftStatus
stackResourceDrift_stackResourceDriftStatus :: Lens' StackResourceDrift StackResourceDriftStatus
stackResourceDrift_stackResourceDriftStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackResourceDrift' {StackResourceDriftStatus
stackResourceDriftStatus :: StackResourceDriftStatus
$sel:stackResourceDriftStatus:StackResourceDrift' :: StackResourceDrift -> StackResourceDriftStatus
stackResourceDriftStatus} -> StackResourceDriftStatus
stackResourceDriftStatus) (\s :: StackResourceDrift
s@StackResourceDrift' {} StackResourceDriftStatus
a -> StackResourceDrift
s {$sel:stackResourceDriftStatus:StackResourceDrift' :: StackResourceDriftStatus
stackResourceDriftStatus = StackResourceDriftStatus
a} :: StackResourceDrift)
stackResourceDrift_timestamp :: Lens.Lens' StackResourceDrift Prelude.UTCTime
stackResourceDrift_timestamp :: Lens' StackResourceDrift UTCTime
stackResourceDrift_timestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StackResourceDrift' {ISO8601
timestamp :: ISO8601
$sel:timestamp:StackResourceDrift' :: StackResourceDrift -> ISO8601
timestamp} -> ISO8601
timestamp) (\s :: StackResourceDrift
s@StackResourceDrift' {} ISO8601
a -> StackResourceDrift
s {$sel:timestamp:StackResourceDrift' :: ISO8601
timestamp = ISO8601
a} :: StackResourceDrift) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
instance Data.FromXML StackResourceDrift where
parseXML :: [Node] -> Either String StackResourceDrift
parseXML [Node]
x =
Maybe Text
-> Maybe Text
-> Maybe ModuleInfo
-> Maybe Text
-> Maybe [PhysicalResourceIdContextKeyValuePair]
-> Maybe [PropertyDifference]
-> Text
-> Text
-> Text
-> StackResourceDriftStatus
-> ISO8601
-> StackResourceDrift
StackResourceDrift'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ActualProperties")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ExpectedProperties")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ModuleInfo")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PhysicalResourceId")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PhysicalResourceIdContext"
forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PropertyDifferences"
forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"StackId")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"LogicalResourceId")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"ResourceType")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"StackResourceDriftStatus")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"Timestamp")
instance Prelude.Hashable StackResourceDrift where
hashWithSalt :: Int -> StackResourceDrift -> Int
hashWithSalt Int
_salt StackResourceDrift' {Maybe [PhysicalResourceIdContextKeyValuePair]
Maybe [PropertyDifference]
Maybe Text
Maybe ModuleInfo
Text
ISO8601
StackResourceDriftStatus
timestamp :: ISO8601
stackResourceDriftStatus :: StackResourceDriftStatus
resourceType :: Text
logicalResourceId :: Text
stackId :: Text
propertyDifferences :: Maybe [PropertyDifference]
physicalResourceIdContext :: Maybe [PhysicalResourceIdContextKeyValuePair]
physicalResourceId :: Maybe Text
moduleInfo :: Maybe ModuleInfo
expectedProperties :: Maybe Text
actualProperties :: Maybe Text
$sel:timestamp:StackResourceDrift' :: StackResourceDrift -> ISO8601
$sel:stackResourceDriftStatus:StackResourceDrift' :: StackResourceDrift -> StackResourceDriftStatus
$sel:resourceType:StackResourceDrift' :: StackResourceDrift -> Text
$sel:logicalResourceId:StackResourceDrift' :: StackResourceDrift -> Text
$sel:stackId:StackResourceDrift' :: StackResourceDrift -> Text
$sel:propertyDifferences:StackResourceDrift' :: StackResourceDrift -> Maybe [PropertyDifference]
$sel:physicalResourceIdContext:StackResourceDrift' :: StackResourceDrift -> Maybe [PhysicalResourceIdContextKeyValuePair]
$sel:physicalResourceId:StackResourceDrift' :: StackResourceDrift -> Maybe Text
$sel:moduleInfo:StackResourceDrift' :: StackResourceDrift -> Maybe ModuleInfo
$sel:expectedProperties:StackResourceDrift' :: StackResourceDrift -> Maybe Text
$sel:actualProperties:StackResourceDrift' :: StackResourceDrift -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
actualProperties
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
expectedProperties
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ModuleInfo
moduleInfo
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
physicalResourceId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PhysicalResourceIdContextKeyValuePair]
physicalResourceIdContext
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PropertyDifference]
propertyDifferences
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stackId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
logicalResourceId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceType
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` StackResourceDriftStatus
stackResourceDriftStatus
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ISO8601
timestamp
instance Prelude.NFData StackResourceDrift where
rnf :: StackResourceDrift -> ()
rnf StackResourceDrift' {Maybe [PhysicalResourceIdContextKeyValuePair]
Maybe [PropertyDifference]
Maybe Text
Maybe ModuleInfo
Text
ISO8601
StackResourceDriftStatus
timestamp :: ISO8601
stackResourceDriftStatus :: StackResourceDriftStatus
resourceType :: Text
logicalResourceId :: Text
stackId :: Text
propertyDifferences :: Maybe [PropertyDifference]
physicalResourceIdContext :: Maybe [PhysicalResourceIdContextKeyValuePair]
physicalResourceId :: Maybe Text
moduleInfo :: Maybe ModuleInfo
expectedProperties :: Maybe Text
actualProperties :: Maybe Text
$sel:timestamp:StackResourceDrift' :: StackResourceDrift -> ISO8601
$sel:stackResourceDriftStatus:StackResourceDrift' :: StackResourceDrift -> StackResourceDriftStatus
$sel:resourceType:StackResourceDrift' :: StackResourceDrift -> Text
$sel:logicalResourceId:StackResourceDrift' :: StackResourceDrift -> Text
$sel:stackId:StackResourceDrift' :: StackResourceDrift -> Text
$sel:propertyDifferences:StackResourceDrift' :: StackResourceDrift -> Maybe [PropertyDifference]
$sel:physicalResourceIdContext:StackResourceDrift' :: StackResourceDrift -> Maybe [PhysicalResourceIdContextKeyValuePair]
$sel:physicalResourceId:StackResourceDrift' :: StackResourceDrift -> Maybe Text
$sel:moduleInfo:StackResourceDrift' :: StackResourceDrift -> Maybe ModuleInfo
$sel:expectedProperties:StackResourceDrift' :: StackResourceDrift -> Maybe Text
$sel:actualProperties:StackResourceDrift' :: StackResourceDrift -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
actualProperties
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
expectedProperties
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ModuleInfo
moduleInfo
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
physicalResourceId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PhysicalResourceIdContextKeyValuePair]
physicalResourceIdContext
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PropertyDifference]
propertyDifferences
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
stackId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
logicalResourceId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceType
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf StackResourceDriftStatus
stackResourceDriftStatus
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ISO8601
timestamp