{-# 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.DynamoDB.Types.SSEDescription where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DynamoDB.Types.AttributeValue
import Amazonka.DynamoDB.Types.SSEStatus
import Amazonka.DynamoDB.Types.SSEType
import Amazonka.DynamoDB.Types.WriteRequest
import qualified Amazonka.Prelude as Prelude
data SSEDescription = SSEDescription'
{
SSEDescription -> Maybe POSIX
inaccessibleEncryptionDateTime :: Prelude.Maybe Data.POSIX,
SSEDescription -> Maybe Text
kmsMasterKeyArn :: Prelude.Maybe Prelude.Text,
SSEDescription -> Maybe SSEType
sSEType :: Prelude.Maybe SSEType,
SSEDescription -> Maybe SSEStatus
status :: Prelude.Maybe SSEStatus
}
deriving (SSEDescription -> SSEDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SSEDescription -> SSEDescription -> Bool
$c/= :: SSEDescription -> SSEDescription -> Bool
== :: SSEDescription -> SSEDescription -> Bool
$c== :: SSEDescription -> SSEDescription -> Bool
Prelude.Eq, ReadPrec [SSEDescription]
ReadPrec SSEDescription
Int -> ReadS SSEDescription
ReadS [SSEDescription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SSEDescription]
$creadListPrec :: ReadPrec [SSEDescription]
readPrec :: ReadPrec SSEDescription
$creadPrec :: ReadPrec SSEDescription
readList :: ReadS [SSEDescription]
$creadList :: ReadS [SSEDescription]
readsPrec :: Int -> ReadS SSEDescription
$creadsPrec :: Int -> ReadS SSEDescription
Prelude.Read, Int -> SSEDescription -> ShowS
[SSEDescription] -> ShowS
SSEDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SSEDescription] -> ShowS
$cshowList :: [SSEDescription] -> ShowS
show :: SSEDescription -> String
$cshow :: SSEDescription -> String
showsPrec :: Int -> SSEDescription -> ShowS
$cshowsPrec :: Int -> SSEDescription -> ShowS
Prelude.Show, forall x. Rep SSEDescription x -> SSEDescription
forall x. SSEDescription -> Rep SSEDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SSEDescription x -> SSEDescription
$cfrom :: forall x. SSEDescription -> Rep SSEDescription x
Prelude.Generic)
newSSEDescription ::
SSEDescription
newSSEDescription :: SSEDescription
newSSEDescription =
SSEDescription'
{ $sel:inaccessibleEncryptionDateTime:SSEDescription' :: Maybe POSIX
inaccessibleEncryptionDateTime =
forall a. Maybe a
Prelude.Nothing,
$sel:kmsMasterKeyArn:SSEDescription' :: Maybe Text
kmsMasterKeyArn = forall a. Maybe a
Prelude.Nothing,
$sel:sSEType:SSEDescription' :: Maybe SSEType
sSEType = forall a. Maybe a
Prelude.Nothing,
$sel:status:SSEDescription' :: Maybe SSEStatus
status = forall a. Maybe a
Prelude.Nothing
}
sSEDescription_inaccessibleEncryptionDateTime :: Lens.Lens' SSEDescription (Prelude.Maybe Prelude.UTCTime)
sSEDescription_inaccessibleEncryptionDateTime :: Lens' SSEDescription (Maybe UTCTime)
sSEDescription_inaccessibleEncryptionDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SSEDescription' {Maybe POSIX
inaccessibleEncryptionDateTime :: Maybe POSIX
$sel:inaccessibleEncryptionDateTime:SSEDescription' :: SSEDescription -> Maybe POSIX
inaccessibleEncryptionDateTime} -> Maybe POSIX
inaccessibleEncryptionDateTime) (\s :: SSEDescription
s@SSEDescription' {} Maybe POSIX
a -> SSEDescription
s {$sel:inaccessibleEncryptionDateTime:SSEDescription' :: Maybe POSIX
inaccessibleEncryptionDateTime = Maybe POSIX
a} :: SSEDescription) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time
sSEDescription_kmsMasterKeyArn :: Lens.Lens' SSEDescription (Prelude.Maybe Prelude.Text)
sSEDescription_kmsMasterKeyArn :: Lens' SSEDescription (Maybe Text)
sSEDescription_kmsMasterKeyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SSEDescription' {Maybe Text
kmsMasterKeyArn :: Maybe Text
$sel:kmsMasterKeyArn:SSEDescription' :: SSEDescription -> Maybe Text
kmsMasterKeyArn} -> Maybe Text
kmsMasterKeyArn) (\s :: SSEDescription
s@SSEDescription' {} Maybe Text
a -> SSEDescription
s {$sel:kmsMasterKeyArn:SSEDescription' :: Maybe Text
kmsMasterKeyArn = Maybe Text
a} :: SSEDescription)
sSEDescription_sSEType :: Lens.Lens' SSEDescription (Prelude.Maybe SSEType)
sSEDescription_sSEType :: Lens' SSEDescription (Maybe SSEType)
sSEDescription_sSEType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SSEDescription' {Maybe SSEType
sSEType :: Maybe SSEType
$sel:sSEType:SSEDescription' :: SSEDescription -> Maybe SSEType
sSEType} -> Maybe SSEType
sSEType) (\s :: SSEDescription
s@SSEDescription' {} Maybe SSEType
a -> SSEDescription
s {$sel:sSEType:SSEDescription' :: Maybe SSEType
sSEType = Maybe SSEType
a} :: SSEDescription)
sSEDescription_status :: Lens.Lens' SSEDescription (Prelude.Maybe SSEStatus)
sSEDescription_status :: Lens' SSEDescription (Maybe SSEStatus)
sSEDescription_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SSEDescription' {Maybe SSEStatus
status :: Maybe SSEStatus
$sel:status:SSEDescription' :: SSEDescription -> Maybe SSEStatus
status} -> Maybe SSEStatus
status) (\s :: SSEDescription
s@SSEDescription' {} Maybe SSEStatus
a -> SSEDescription
s {$sel:status:SSEDescription' :: Maybe SSEStatus
status = Maybe SSEStatus
a} :: SSEDescription)
instance Data.FromJSON SSEDescription where
parseJSON :: Value -> Parser SSEDescription
parseJSON =
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
String
"SSEDescription"
( \Object
x ->
Maybe POSIX
-> Maybe Text -> Maybe SSEType -> Maybe SSEStatus -> SSEDescription
SSEDescription'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"InaccessibleEncryptionDateTime")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"KMSMasterKeyArn")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"SSEType")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Status")
)
instance Prelude.Hashable SSEDescription where
hashWithSalt :: Int -> SSEDescription -> Int
hashWithSalt Int
_salt SSEDescription' {Maybe Text
Maybe POSIX
Maybe SSEType
Maybe SSEStatus
status :: Maybe SSEStatus
sSEType :: Maybe SSEType
kmsMasterKeyArn :: Maybe Text
inaccessibleEncryptionDateTime :: Maybe POSIX
$sel:status:SSEDescription' :: SSEDescription -> Maybe SSEStatus
$sel:sSEType:SSEDescription' :: SSEDescription -> Maybe SSEType
$sel:kmsMasterKeyArn:SSEDescription' :: SSEDescription -> Maybe Text
$sel:inaccessibleEncryptionDateTime:SSEDescription' :: SSEDescription -> Maybe POSIX
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
inaccessibleEncryptionDateTime
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsMasterKeyArn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SSEType
sSEType
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SSEStatus
status
instance Prelude.NFData SSEDescription where
rnf :: SSEDescription -> ()
rnf SSEDescription' {Maybe Text
Maybe POSIX
Maybe SSEType
Maybe SSEStatus
status :: Maybe SSEStatus
sSEType :: Maybe SSEType
kmsMasterKeyArn :: Maybe Text
inaccessibleEncryptionDateTime :: Maybe POSIX
$sel:status:SSEDescription' :: SSEDescription -> Maybe SSEStatus
$sel:sSEType:SSEDescription' :: SSEDescription -> Maybe SSEType
$sel:kmsMasterKeyArn:SSEDescription' :: SSEDescription -> Maybe Text
$sel:inaccessibleEncryptionDateTime:SSEDescription' :: SSEDescription -> Maybe POSIX
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
inaccessibleEncryptionDateTime
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsMasterKeyArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SSEType
sSEType
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SSEStatus
status