{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Firehose.Types.DeliveryStreamEncryptionConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Firehose.Types.DeliveryStreamEncryptionConfiguration where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Firehose.Types.DeliveryStreamEncryptionStatus
import Amazonka.Firehose.Types.FailureDescription
import Amazonka.Firehose.Types.KeyType
import qualified Amazonka.Prelude as Prelude

-- | Contains information about the server-side encryption (SSE) status for
-- the delivery stream, the type customer master key (CMK) in use, if any,
-- and the ARN of the CMK. You can get
-- @DeliveryStreamEncryptionConfiguration@ by invoking the
-- DescribeDeliveryStream operation.
--
-- /See:/ 'newDeliveryStreamEncryptionConfiguration' smart constructor.
data DeliveryStreamEncryptionConfiguration = DeliveryStreamEncryptionConfiguration'
  { -- | Provides details in case one of the following operations fails due to an
    -- error related to KMS: CreateDeliveryStream, DeleteDeliveryStream,
    -- StartDeliveryStreamEncryption, StopDeliveryStreamEncryption.
    DeliveryStreamEncryptionConfiguration -> Maybe FailureDescription
failureDescription :: Prelude.Maybe FailureDescription,
    -- | If @KeyType@ is @CUSTOMER_MANAGED_CMK@, this field contains the ARN of
    -- the customer managed CMK. If @KeyType@ is
    -- @Amazon Web Services_OWNED_CMK@, @DeliveryStreamEncryptionConfiguration@
    -- doesn\'t contain a value for @KeyARN@.
    DeliveryStreamEncryptionConfiguration -> Maybe Text
keyARN :: Prelude.Maybe Prelude.Text,
    -- | Indicates the type of customer master key (CMK) that is used for
    -- encryption. The default setting is @Amazon Web Services_OWNED_CMK@. For
    -- more information about CMKs, see
    -- <https://docs.aws.amazon.com/kms/latest/developerguide/concepts.html#master_keys Customer Master Keys (CMKs)>.
    DeliveryStreamEncryptionConfiguration -> Maybe KeyType
keyType :: Prelude.Maybe KeyType,
    -- | This is the server-side encryption (SSE) status for the delivery stream.
    -- For a full description of the different values of this status, see
    -- StartDeliveryStreamEncryption and StopDeliveryStreamEncryption. If this
    -- status is @ENABLING_FAILED@ or @DISABLING_FAILED@, it is the status of
    -- the most recent attempt to enable or disable SSE, respectively.
    DeliveryStreamEncryptionConfiguration
-> Maybe DeliveryStreamEncryptionStatus
status :: Prelude.Maybe DeliveryStreamEncryptionStatus
  }
  deriving (DeliveryStreamEncryptionConfiguration
-> DeliveryStreamEncryptionConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeliveryStreamEncryptionConfiguration
-> DeliveryStreamEncryptionConfiguration -> Bool
$c/= :: DeliveryStreamEncryptionConfiguration
-> DeliveryStreamEncryptionConfiguration -> Bool
== :: DeliveryStreamEncryptionConfiguration
-> DeliveryStreamEncryptionConfiguration -> Bool
$c== :: DeliveryStreamEncryptionConfiguration
-> DeliveryStreamEncryptionConfiguration -> Bool
Prelude.Eq, ReadPrec [DeliveryStreamEncryptionConfiguration]
ReadPrec DeliveryStreamEncryptionConfiguration
Int -> ReadS DeliveryStreamEncryptionConfiguration
ReadS [DeliveryStreamEncryptionConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeliveryStreamEncryptionConfiguration]
$creadListPrec :: ReadPrec [DeliveryStreamEncryptionConfiguration]
readPrec :: ReadPrec DeliveryStreamEncryptionConfiguration
$creadPrec :: ReadPrec DeliveryStreamEncryptionConfiguration
readList :: ReadS [DeliveryStreamEncryptionConfiguration]
$creadList :: ReadS [DeliveryStreamEncryptionConfiguration]
readsPrec :: Int -> ReadS DeliveryStreamEncryptionConfiguration
$creadsPrec :: Int -> ReadS DeliveryStreamEncryptionConfiguration
Prelude.Read, Int -> DeliveryStreamEncryptionConfiguration -> ShowS
[DeliveryStreamEncryptionConfiguration] -> ShowS
DeliveryStreamEncryptionConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeliveryStreamEncryptionConfiguration] -> ShowS
$cshowList :: [DeliveryStreamEncryptionConfiguration] -> ShowS
show :: DeliveryStreamEncryptionConfiguration -> String
$cshow :: DeliveryStreamEncryptionConfiguration -> String
showsPrec :: Int -> DeliveryStreamEncryptionConfiguration -> ShowS
$cshowsPrec :: Int -> DeliveryStreamEncryptionConfiguration -> ShowS
Prelude.Show, forall x.
Rep DeliveryStreamEncryptionConfiguration x
-> DeliveryStreamEncryptionConfiguration
forall x.
DeliveryStreamEncryptionConfiguration
-> Rep DeliveryStreamEncryptionConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeliveryStreamEncryptionConfiguration x
-> DeliveryStreamEncryptionConfiguration
$cfrom :: forall x.
DeliveryStreamEncryptionConfiguration
-> Rep DeliveryStreamEncryptionConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'DeliveryStreamEncryptionConfiguration' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'failureDescription', 'deliveryStreamEncryptionConfiguration_failureDescription' - Provides details in case one of the following operations fails due to an
-- error related to KMS: CreateDeliveryStream, DeleteDeliveryStream,
-- StartDeliveryStreamEncryption, StopDeliveryStreamEncryption.
--
-- 'keyARN', 'deliveryStreamEncryptionConfiguration_keyARN' - If @KeyType@ is @CUSTOMER_MANAGED_CMK@, this field contains the ARN of
-- the customer managed CMK. If @KeyType@ is
-- @Amazon Web Services_OWNED_CMK@, @DeliveryStreamEncryptionConfiguration@
-- doesn\'t contain a value for @KeyARN@.
--
-- 'keyType', 'deliveryStreamEncryptionConfiguration_keyType' - Indicates the type of customer master key (CMK) that is used for
-- encryption. The default setting is @Amazon Web Services_OWNED_CMK@. For
-- more information about CMKs, see
-- <https://docs.aws.amazon.com/kms/latest/developerguide/concepts.html#master_keys Customer Master Keys (CMKs)>.
--
-- 'status', 'deliveryStreamEncryptionConfiguration_status' - This is the server-side encryption (SSE) status for the delivery stream.
-- For a full description of the different values of this status, see
-- StartDeliveryStreamEncryption and StopDeliveryStreamEncryption. If this
-- status is @ENABLING_FAILED@ or @DISABLING_FAILED@, it is the status of
-- the most recent attempt to enable or disable SSE, respectively.
newDeliveryStreamEncryptionConfiguration ::
  DeliveryStreamEncryptionConfiguration
newDeliveryStreamEncryptionConfiguration :: DeliveryStreamEncryptionConfiguration
newDeliveryStreamEncryptionConfiguration =
  DeliveryStreamEncryptionConfiguration'
    { $sel:failureDescription:DeliveryStreamEncryptionConfiguration' :: Maybe FailureDescription
failureDescription =
        forall a. Maybe a
Prelude.Nothing,
      $sel:keyARN:DeliveryStreamEncryptionConfiguration' :: Maybe Text
keyARN = forall a. Maybe a
Prelude.Nothing,
      $sel:keyType:DeliveryStreamEncryptionConfiguration' :: Maybe KeyType
keyType = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DeliveryStreamEncryptionConfiguration' :: Maybe DeliveryStreamEncryptionStatus
status = forall a. Maybe a
Prelude.Nothing
    }

-- | Provides details in case one of the following operations fails due to an
-- error related to KMS: CreateDeliveryStream, DeleteDeliveryStream,
-- StartDeliveryStreamEncryption, StopDeliveryStreamEncryption.
deliveryStreamEncryptionConfiguration_failureDescription :: Lens.Lens' DeliveryStreamEncryptionConfiguration (Prelude.Maybe FailureDescription)
deliveryStreamEncryptionConfiguration_failureDescription :: Lens'
  DeliveryStreamEncryptionConfiguration (Maybe FailureDescription)
deliveryStreamEncryptionConfiguration_failureDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamEncryptionConfiguration' {Maybe FailureDescription
failureDescription :: Maybe FailureDescription
$sel:failureDescription:DeliveryStreamEncryptionConfiguration' :: DeliveryStreamEncryptionConfiguration -> Maybe FailureDescription
failureDescription} -> Maybe FailureDescription
failureDescription) (\s :: DeliveryStreamEncryptionConfiguration
s@DeliveryStreamEncryptionConfiguration' {} Maybe FailureDescription
a -> DeliveryStreamEncryptionConfiguration
s {$sel:failureDescription:DeliveryStreamEncryptionConfiguration' :: Maybe FailureDescription
failureDescription = Maybe FailureDescription
a} :: DeliveryStreamEncryptionConfiguration)

-- | If @KeyType@ is @CUSTOMER_MANAGED_CMK@, this field contains the ARN of
-- the customer managed CMK. If @KeyType@ is
-- @Amazon Web Services_OWNED_CMK@, @DeliveryStreamEncryptionConfiguration@
-- doesn\'t contain a value for @KeyARN@.
deliveryStreamEncryptionConfiguration_keyARN :: Lens.Lens' DeliveryStreamEncryptionConfiguration (Prelude.Maybe Prelude.Text)
deliveryStreamEncryptionConfiguration_keyARN :: Lens' DeliveryStreamEncryptionConfiguration (Maybe Text)
deliveryStreamEncryptionConfiguration_keyARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamEncryptionConfiguration' {Maybe Text
keyARN :: Maybe Text
$sel:keyARN:DeliveryStreamEncryptionConfiguration' :: DeliveryStreamEncryptionConfiguration -> Maybe Text
keyARN} -> Maybe Text
keyARN) (\s :: DeliveryStreamEncryptionConfiguration
s@DeliveryStreamEncryptionConfiguration' {} Maybe Text
a -> DeliveryStreamEncryptionConfiguration
s {$sel:keyARN:DeliveryStreamEncryptionConfiguration' :: Maybe Text
keyARN = Maybe Text
a} :: DeliveryStreamEncryptionConfiguration)

-- | Indicates the type of customer master key (CMK) that is used for
-- encryption. The default setting is @Amazon Web Services_OWNED_CMK@. For
-- more information about CMKs, see
-- <https://docs.aws.amazon.com/kms/latest/developerguide/concepts.html#master_keys Customer Master Keys (CMKs)>.
deliveryStreamEncryptionConfiguration_keyType :: Lens.Lens' DeliveryStreamEncryptionConfiguration (Prelude.Maybe KeyType)
deliveryStreamEncryptionConfiguration_keyType :: Lens' DeliveryStreamEncryptionConfiguration (Maybe KeyType)
deliveryStreamEncryptionConfiguration_keyType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamEncryptionConfiguration' {Maybe KeyType
keyType :: Maybe KeyType
$sel:keyType:DeliveryStreamEncryptionConfiguration' :: DeliveryStreamEncryptionConfiguration -> Maybe KeyType
keyType} -> Maybe KeyType
keyType) (\s :: DeliveryStreamEncryptionConfiguration
s@DeliveryStreamEncryptionConfiguration' {} Maybe KeyType
a -> DeliveryStreamEncryptionConfiguration
s {$sel:keyType:DeliveryStreamEncryptionConfiguration' :: Maybe KeyType
keyType = Maybe KeyType
a} :: DeliveryStreamEncryptionConfiguration)

-- | This is the server-side encryption (SSE) status for the delivery stream.
-- For a full description of the different values of this status, see
-- StartDeliveryStreamEncryption and StopDeliveryStreamEncryption. If this
-- status is @ENABLING_FAILED@ or @DISABLING_FAILED@, it is the status of
-- the most recent attempt to enable or disable SSE, respectively.
deliveryStreamEncryptionConfiguration_status :: Lens.Lens' DeliveryStreamEncryptionConfiguration (Prelude.Maybe DeliveryStreamEncryptionStatus)
deliveryStreamEncryptionConfiguration_status :: Lens'
  DeliveryStreamEncryptionConfiguration
  (Maybe DeliveryStreamEncryptionStatus)
deliveryStreamEncryptionConfiguration_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamEncryptionConfiguration' {Maybe DeliveryStreamEncryptionStatus
status :: Maybe DeliveryStreamEncryptionStatus
$sel:status:DeliveryStreamEncryptionConfiguration' :: DeliveryStreamEncryptionConfiguration
-> Maybe DeliveryStreamEncryptionStatus
status} -> Maybe DeliveryStreamEncryptionStatus
status) (\s :: DeliveryStreamEncryptionConfiguration
s@DeliveryStreamEncryptionConfiguration' {} Maybe DeliveryStreamEncryptionStatus
a -> DeliveryStreamEncryptionConfiguration
s {$sel:status:DeliveryStreamEncryptionConfiguration' :: Maybe DeliveryStreamEncryptionStatus
status = Maybe DeliveryStreamEncryptionStatus
a} :: DeliveryStreamEncryptionConfiguration)

instance
  Data.FromJSON
    DeliveryStreamEncryptionConfiguration
  where
  parseJSON :: Value -> Parser DeliveryStreamEncryptionConfiguration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DeliveryStreamEncryptionConfiguration"
      ( \Object
x ->
          Maybe FailureDescription
-> Maybe Text
-> Maybe KeyType
-> Maybe DeliveryStreamEncryptionStatus
-> DeliveryStreamEncryptionConfiguration
DeliveryStreamEncryptionConfiguration'
            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
"FailureDescription")
            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
"KeyARN")
            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
"KeyType")
            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
    DeliveryStreamEncryptionConfiguration
  where
  hashWithSalt :: Int -> DeliveryStreamEncryptionConfiguration -> Int
hashWithSalt
    Int
_salt
    DeliveryStreamEncryptionConfiguration' {Maybe Text
Maybe DeliveryStreamEncryptionStatus
Maybe FailureDescription
Maybe KeyType
status :: Maybe DeliveryStreamEncryptionStatus
keyType :: Maybe KeyType
keyARN :: Maybe Text
failureDescription :: Maybe FailureDescription
$sel:status:DeliveryStreamEncryptionConfiguration' :: DeliveryStreamEncryptionConfiguration
-> Maybe DeliveryStreamEncryptionStatus
$sel:keyType:DeliveryStreamEncryptionConfiguration' :: DeliveryStreamEncryptionConfiguration -> Maybe KeyType
$sel:keyARN:DeliveryStreamEncryptionConfiguration' :: DeliveryStreamEncryptionConfiguration -> Maybe Text
$sel:failureDescription:DeliveryStreamEncryptionConfiguration' :: DeliveryStreamEncryptionConfiguration -> Maybe FailureDescription
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FailureDescription
failureDescription
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
keyARN
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe KeyType
keyType
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeliveryStreamEncryptionStatus
status

instance
  Prelude.NFData
    DeliveryStreamEncryptionConfiguration
  where
  rnf :: DeliveryStreamEncryptionConfiguration -> ()
rnf DeliveryStreamEncryptionConfiguration' {Maybe Text
Maybe DeliveryStreamEncryptionStatus
Maybe FailureDescription
Maybe KeyType
status :: Maybe DeliveryStreamEncryptionStatus
keyType :: Maybe KeyType
keyARN :: Maybe Text
failureDescription :: Maybe FailureDescription
$sel:status:DeliveryStreamEncryptionConfiguration' :: DeliveryStreamEncryptionConfiguration
-> Maybe DeliveryStreamEncryptionStatus
$sel:keyType:DeliveryStreamEncryptionConfiguration' :: DeliveryStreamEncryptionConfiguration -> Maybe KeyType
$sel:keyARN:DeliveryStreamEncryptionConfiguration' :: DeliveryStreamEncryptionConfiguration -> Maybe Text
$sel:failureDescription:DeliveryStreamEncryptionConfiguration' :: DeliveryStreamEncryptionConfiguration -> Maybe FailureDescription
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe FailureDescription
failureDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
keyARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe KeyType
keyType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeliveryStreamEncryptionStatus
status