{-# 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.DeliveryStreamDescription
-- 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.DeliveryStreamDescription 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.DeliveryStreamEncryptionConfiguration
import Amazonka.Firehose.Types.DeliveryStreamStatus
import Amazonka.Firehose.Types.DeliveryStreamType
import Amazonka.Firehose.Types.DestinationDescription
import Amazonka.Firehose.Types.FailureDescription
import Amazonka.Firehose.Types.SourceDescription
import qualified Amazonka.Prelude as Prelude

-- | Contains information about a delivery stream.
--
-- /See:/ 'newDeliveryStreamDescription' smart constructor.
data DeliveryStreamDescription = DeliveryStreamDescription'
  { -- | The date and time that the delivery stream was created.
    DeliveryStreamDescription -> Maybe POSIX
createTimestamp :: Prelude.Maybe Data.POSIX,
    -- | Indicates the server-side encryption (SSE) status for the delivery
    -- stream.
    DeliveryStreamDescription
-> Maybe DeliveryStreamEncryptionConfiguration
deliveryStreamEncryptionConfiguration :: Prelude.Maybe DeliveryStreamEncryptionConfiguration,
    -- | Provides details in case one of the following operations fails due to an
    -- error related to KMS: CreateDeliveryStream, DeleteDeliveryStream,
    -- StartDeliveryStreamEncryption, StopDeliveryStreamEncryption.
    DeliveryStreamDescription -> Maybe FailureDescription
failureDescription :: Prelude.Maybe FailureDescription,
    -- | The date and time that the delivery stream was last updated.
    DeliveryStreamDescription -> Maybe POSIX
lastUpdateTimestamp :: Prelude.Maybe Data.POSIX,
    -- | If the @DeliveryStreamType@ parameter is @KinesisStreamAsSource@, a
    -- SourceDescription object describing the source Kinesis data stream.
    DeliveryStreamDescription -> Maybe SourceDescription
source :: Prelude.Maybe SourceDescription,
    -- | The name of the delivery stream.
    DeliveryStreamDescription -> Text
deliveryStreamName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the delivery stream. For more
    -- information, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs) and Amazon Web Services Service Namespaces>.
    DeliveryStreamDescription -> Text
deliveryStreamARN :: Prelude.Text,
    -- | The status of the delivery stream. If the status of a delivery stream is
    -- @CREATING_FAILED@, this status doesn\'t change, and you can\'t invoke
    -- @CreateDeliveryStream@ again on it. However, you can invoke the
    -- DeleteDeliveryStream operation to delete it.
    DeliveryStreamDescription -> DeliveryStreamStatus
deliveryStreamStatus :: DeliveryStreamStatus,
    -- | The delivery stream type. This can be one of the following values:
    --
    -- -   @DirectPut@: Provider applications access the delivery stream
    --     directly.
    --
    -- -   @KinesisStreamAsSource@: The delivery stream uses a Kinesis data
    --     stream as a source.
    DeliveryStreamDescription -> DeliveryStreamType
deliveryStreamType :: DeliveryStreamType,
    -- | Each time the destination is updated for a delivery stream, the version
    -- ID is changed, and the current version ID is required when updating the
    -- destination. This is so that the service knows it is applying the
    -- changes to the correct version of the delivery stream.
    DeliveryStreamDescription -> Text
versionId :: Prelude.Text,
    -- | The destinations.
    DeliveryStreamDescription -> [DestinationDescription]
destinations :: [DestinationDescription],
    -- | Indicates whether there are more destinations available to list.
    DeliveryStreamDescription -> Bool
hasMoreDestinations :: Prelude.Bool
  }
  deriving (DeliveryStreamDescription -> DeliveryStreamDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeliveryStreamDescription -> DeliveryStreamDescription -> Bool
$c/= :: DeliveryStreamDescription -> DeliveryStreamDescription -> Bool
== :: DeliveryStreamDescription -> DeliveryStreamDescription -> Bool
$c== :: DeliveryStreamDescription -> DeliveryStreamDescription -> Bool
Prelude.Eq, Int -> DeliveryStreamDescription -> ShowS
[DeliveryStreamDescription] -> ShowS
DeliveryStreamDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeliveryStreamDescription] -> ShowS
$cshowList :: [DeliveryStreamDescription] -> ShowS
show :: DeliveryStreamDescription -> String
$cshow :: DeliveryStreamDescription -> String
showsPrec :: Int -> DeliveryStreamDescription -> ShowS
$cshowsPrec :: Int -> DeliveryStreamDescription -> ShowS
Prelude.Show, forall x.
Rep DeliveryStreamDescription x -> DeliveryStreamDescription
forall x.
DeliveryStreamDescription -> Rep DeliveryStreamDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeliveryStreamDescription x -> DeliveryStreamDescription
$cfrom :: forall x.
DeliveryStreamDescription -> Rep DeliveryStreamDescription x
Prelude.Generic)

-- |
-- Create a value of 'DeliveryStreamDescription' 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:
--
-- 'createTimestamp', 'deliveryStreamDescription_createTimestamp' - The date and time that the delivery stream was created.
--
-- 'deliveryStreamEncryptionConfiguration', 'deliveryStreamDescription_deliveryStreamEncryptionConfiguration' - Indicates the server-side encryption (SSE) status for the delivery
-- stream.
--
-- 'failureDescription', 'deliveryStreamDescription_failureDescription' - Provides details in case one of the following operations fails due to an
-- error related to KMS: CreateDeliveryStream, DeleteDeliveryStream,
-- StartDeliveryStreamEncryption, StopDeliveryStreamEncryption.
--
-- 'lastUpdateTimestamp', 'deliveryStreamDescription_lastUpdateTimestamp' - The date and time that the delivery stream was last updated.
--
-- 'source', 'deliveryStreamDescription_source' - If the @DeliveryStreamType@ parameter is @KinesisStreamAsSource@, a
-- SourceDescription object describing the source Kinesis data stream.
--
-- 'deliveryStreamName', 'deliveryStreamDescription_deliveryStreamName' - The name of the delivery stream.
--
-- 'deliveryStreamARN', 'deliveryStreamDescription_deliveryStreamARN' - The Amazon Resource Name (ARN) of the delivery stream. For more
-- information, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs) and Amazon Web Services Service Namespaces>.
--
-- 'deliveryStreamStatus', 'deliveryStreamDescription_deliveryStreamStatus' - The status of the delivery stream. If the status of a delivery stream is
-- @CREATING_FAILED@, this status doesn\'t change, and you can\'t invoke
-- @CreateDeliveryStream@ again on it. However, you can invoke the
-- DeleteDeliveryStream operation to delete it.
--
-- 'deliveryStreamType', 'deliveryStreamDescription_deliveryStreamType' - The delivery stream type. This can be one of the following values:
--
-- -   @DirectPut@: Provider applications access the delivery stream
--     directly.
--
-- -   @KinesisStreamAsSource@: The delivery stream uses a Kinesis data
--     stream as a source.
--
-- 'versionId', 'deliveryStreamDescription_versionId' - Each time the destination is updated for a delivery stream, the version
-- ID is changed, and the current version ID is required when updating the
-- destination. This is so that the service knows it is applying the
-- changes to the correct version of the delivery stream.
--
-- 'destinations', 'deliveryStreamDescription_destinations' - The destinations.
--
-- 'hasMoreDestinations', 'deliveryStreamDescription_hasMoreDestinations' - Indicates whether there are more destinations available to list.
newDeliveryStreamDescription ::
  -- | 'deliveryStreamName'
  Prelude.Text ->
  -- | 'deliveryStreamARN'
  Prelude.Text ->
  -- | 'deliveryStreamStatus'
  DeliveryStreamStatus ->
  -- | 'deliveryStreamType'
  DeliveryStreamType ->
  -- | 'versionId'
  Prelude.Text ->
  -- | 'hasMoreDestinations'
  Prelude.Bool ->
  DeliveryStreamDescription
newDeliveryStreamDescription :: Text
-> Text
-> DeliveryStreamStatus
-> DeliveryStreamType
-> Text
-> Bool
-> DeliveryStreamDescription
newDeliveryStreamDescription
  Text
pDeliveryStreamName_
  Text
pDeliveryStreamARN_
  DeliveryStreamStatus
pDeliveryStreamStatus_
  DeliveryStreamType
pDeliveryStreamType_
  Text
pVersionId_
  Bool
pHasMoreDestinations_ =
    DeliveryStreamDescription'
      { $sel:createTimestamp:DeliveryStreamDescription' :: Maybe POSIX
createTimestamp =
          forall a. Maybe a
Prelude.Nothing,
        $sel:deliveryStreamEncryptionConfiguration:DeliveryStreamDescription' :: Maybe DeliveryStreamEncryptionConfiguration
deliveryStreamEncryptionConfiguration =
          forall a. Maybe a
Prelude.Nothing,
        $sel:failureDescription:DeliveryStreamDescription' :: Maybe FailureDescription
failureDescription = forall a. Maybe a
Prelude.Nothing,
        $sel:lastUpdateTimestamp:DeliveryStreamDescription' :: Maybe POSIX
lastUpdateTimestamp = forall a. Maybe a
Prelude.Nothing,
        $sel:source:DeliveryStreamDescription' :: Maybe SourceDescription
source = forall a. Maybe a
Prelude.Nothing,
        $sel:deliveryStreamName:DeliveryStreamDescription' :: Text
deliveryStreamName = Text
pDeliveryStreamName_,
        $sel:deliveryStreamARN:DeliveryStreamDescription' :: Text
deliveryStreamARN = Text
pDeliveryStreamARN_,
        $sel:deliveryStreamStatus:DeliveryStreamDescription' :: DeliveryStreamStatus
deliveryStreamStatus = DeliveryStreamStatus
pDeliveryStreamStatus_,
        $sel:deliveryStreamType:DeliveryStreamDescription' :: DeliveryStreamType
deliveryStreamType = DeliveryStreamType
pDeliveryStreamType_,
        $sel:versionId:DeliveryStreamDescription' :: Text
versionId = Text
pVersionId_,
        $sel:destinations:DeliveryStreamDescription' :: [DestinationDescription]
destinations = forall a. Monoid a => a
Prelude.mempty,
        $sel:hasMoreDestinations:DeliveryStreamDescription' :: Bool
hasMoreDestinations = Bool
pHasMoreDestinations_
      }

-- | The date and time that the delivery stream was created.
deliveryStreamDescription_createTimestamp :: Lens.Lens' DeliveryStreamDescription (Prelude.Maybe Prelude.UTCTime)
deliveryStreamDescription_createTimestamp :: Lens' DeliveryStreamDescription (Maybe UTCTime)
deliveryStreamDescription_createTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamDescription' {Maybe POSIX
createTimestamp :: Maybe POSIX
$sel:createTimestamp:DeliveryStreamDescription' :: DeliveryStreamDescription -> Maybe POSIX
createTimestamp} -> Maybe POSIX
createTimestamp) (\s :: DeliveryStreamDescription
s@DeliveryStreamDescription' {} Maybe POSIX
a -> DeliveryStreamDescription
s {$sel:createTimestamp:DeliveryStreamDescription' :: Maybe POSIX
createTimestamp = Maybe POSIX
a} :: DeliveryStreamDescription) 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

-- | Indicates the server-side encryption (SSE) status for the delivery
-- stream.
deliveryStreamDescription_deliveryStreamEncryptionConfiguration :: Lens.Lens' DeliveryStreamDescription (Prelude.Maybe DeliveryStreamEncryptionConfiguration)
deliveryStreamDescription_deliveryStreamEncryptionConfiguration :: Lens'
  DeliveryStreamDescription
  (Maybe DeliveryStreamEncryptionConfiguration)
deliveryStreamDescription_deliveryStreamEncryptionConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamDescription' {Maybe DeliveryStreamEncryptionConfiguration
deliveryStreamEncryptionConfiguration :: Maybe DeliveryStreamEncryptionConfiguration
$sel:deliveryStreamEncryptionConfiguration:DeliveryStreamDescription' :: DeliveryStreamDescription
-> Maybe DeliveryStreamEncryptionConfiguration
deliveryStreamEncryptionConfiguration} -> Maybe DeliveryStreamEncryptionConfiguration
deliveryStreamEncryptionConfiguration) (\s :: DeliveryStreamDescription
s@DeliveryStreamDescription' {} Maybe DeliveryStreamEncryptionConfiguration
a -> DeliveryStreamDescription
s {$sel:deliveryStreamEncryptionConfiguration:DeliveryStreamDescription' :: Maybe DeliveryStreamEncryptionConfiguration
deliveryStreamEncryptionConfiguration = Maybe DeliveryStreamEncryptionConfiguration
a} :: DeliveryStreamDescription)

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

-- | The date and time that the delivery stream was last updated.
deliveryStreamDescription_lastUpdateTimestamp :: Lens.Lens' DeliveryStreamDescription (Prelude.Maybe Prelude.UTCTime)
deliveryStreamDescription_lastUpdateTimestamp :: Lens' DeliveryStreamDescription (Maybe UTCTime)
deliveryStreamDescription_lastUpdateTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamDescription' {Maybe POSIX
lastUpdateTimestamp :: Maybe POSIX
$sel:lastUpdateTimestamp:DeliveryStreamDescription' :: DeliveryStreamDescription -> Maybe POSIX
lastUpdateTimestamp} -> Maybe POSIX
lastUpdateTimestamp) (\s :: DeliveryStreamDescription
s@DeliveryStreamDescription' {} Maybe POSIX
a -> DeliveryStreamDescription
s {$sel:lastUpdateTimestamp:DeliveryStreamDescription' :: Maybe POSIX
lastUpdateTimestamp = Maybe POSIX
a} :: DeliveryStreamDescription) 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

-- | If the @DeliveryStreamType@ parameter is @KinesisStreamAsSource@, a
-- SourceDescription object describing the source Kinesis data stream.
deliveryStreamDescription_source :: Lens.Lens' DeliveryStreamDescription (Prelude.Maybe SourceDescription)
deliveryStreamDescription_source :: Lens' DeliveryStreamDescription (Maybe SourceDescription)
deliveryStreamDescription_source = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamDescription' {Maybe SourceDescription
source :: Maybe SourceDescription
$sel:source:DeliveryStreamDescription' :: DeliveryStreamDescription -> Maybe SourceDescription
source} -> Maybe SourceDescription
source) (\s :: DeliveryStreamDescription
s@DeliveryStreamDescription' {} Maybe SourceDescription
a -> DeliveryStreamDescription
s {$sel:source:DeliveryStreamDescription' :: Maybe SourceDescription
source = Maybe SourceDescription
a} :: DeliveryStreamDescription)

-- | The name of the delivery stream.
deliveryStreamDescription_deliveryStreamName :: Lens.Lens' DeliveryStreamDescription Prelude.Text
deliveryStreamDescription_deliveryStreamName :: Lens' DeliveryStreamDescription Text
deliveryStreamDescription_deliveryStreamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamDescription' {Text
deliveryStreamName :: Text
$sel:deliveryStreamName:DeliveryStreamDescription' :: DeliveryStreamDescription -> Text
deliveryStreamName} -> Text
deliveryStreamName) (\s :: DeliveryStreamDescription
s@DeliveryStreamDescription' {} Text
a -> DeliveryStreamDescription
s {$sel:deliveryStreamName:DeliveryStreamDescription' :: Text
deliveryStreamName = Text
a} :: DeliveryStreamDescription)

-- | The Amazon Resource Name (ARN) of the delivery stream. For more
-- information, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs) and Amazon Web Services Service Namespaces>.
deliveryStreamDescription_deliveryStreamARN :: Lens.Lens' DeliveryStreamDescription Prelude.Text
deliveryStreamDescription_deliveryStreamARN :: Lens' DeliveryStreamDescription Text
deliveryStreamDescription_deliveryStreamARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamDescription' {Text
deliveryStreamARN :: Text
$sel:deliveryStreamARN:DeliveryStreamDescription' :: DeliveryStreamDescription -> Text
deliveryStreamARN} -> Text
deliveryStreamARN) (\s :: DeliveryStreamDescription
s@DeliveryStreamDescription' {} Text
a -> DeliveryStreamDescription
s {$sel:deliveryStreamARN:DeliveryStreamDescription' :: Text
deliveryStreamARN = Text
a} :: DeliveryStreamDescription)

-- | The status of the delivery stream. If the status of a delivery stream is
-- @CREATING_FAILED@, this status doesn\'t change, and you can\'t invoke
-- @CreateDeliveryStream@ again on it. However, you can invoke the
-- DeleteDeliveryStream operation to delete it.
deliveryStreamDescription_deliveryStreamStatus :: Lens.Lens' DeliveryStreamDescription DeliveryStreamStatus
deliveryStreamDescription_deliveryStreamStatus :: Lens' DeliveryStreamDescription DeliveryStreamStatus
deliveryStreamDescription_deliveryStreamStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamDescription' {DeliveryStreamStatus
deliveryStreamStatus :: DeliveryStreamStatus
$sel:deliveryStreamStatus:DeliveryStreamDescription' :: DeliveryStreamDescription -> DeliveryStreamStatus
deliveryStreamStatus} -> DeliveryStreamStatus
deliveryStreamStatus) (\s :: DeliveryStreamDescription
s@DeliveryStreamDescription' {} DeliveryStreamStatus
a -> DeliveryStreamDescription
s {$sel:deliveryStreamStatus:DeliveryStreamDescription' :: DeliveryStreamStatus
deliveryStreamStatus = DeliveryStreamStatus
a} :: DeliveryStreamDescription)

-- | The delivery stream type. This can be one of the following values:
--
-- -   @DirectPut@: Provider applications access the delivery stream
--     directly.
--
-- -   @KinesisStreamAsSource@: The delivery stream uses a Kinesis data
--     stream as a source.
deliveryStreamDescription_deliveryStreamType :: Lens.Lens' DeliveryStreamDescription DeliveryStreamType
deliveryStreamDescription_deliveryStreamType :: Lens' DeliveryStreamDescription DeliveryStreamType
deliveryStreamDescription_deliveryStreamType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamDescription' {DeliveryStreamType
deliveryStreamType :: DeliveryStreamType
$sel:deliveryStreamType:DeliveryStreamDescription' :: DeliveryStreamDescription -> DeliveryStreamType
deliveryStreamType} -> DeliveryStreamType
deliveryStreamType) (\s :: DeliveryStreamDescription
s@DeliveryStreamDescription' {} DeliveryStreamType
a -> DeliveryStreamDescription
s {$sel:deliveryStreamType:DeliveryStreamDescription' :: DeliveryStreamType
deliveryStreamType = DeliveryStreamType
a} :: DeliveryStreamDescription)

-- | Each time the destination is updated for a delivery stream, the version
-- ID is changed, and the current version ID is required when updating the
-- destination. This is so that the service knows it is applying the
-- changes to the correct version of the delivery stream.
deliveryStreamDescription_versionId :: Lens.Lens' DeliveryStreamDescription Prelude.Text
deliveryStreamDescription_versionId :: Lens' DeliveryStreamDescription Text
deliveryStreamDescription_versionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamDescription' {Text
versionId :: Text
$sel:versionId:DeliveryStreamDescription' :: DeliveryStreamDescription -> Text
versionId} -> Text
versionId) (\s :: DeliveryStreamDescription
s@DeliveryStreamDescription' {} Text
a -> DeliveryStreamDescription
s {$sel:versionId:DeliveryStreamDescription' :: Text
versionId = Text
a} :: DeliveryStreamDescription)

-- | The destinations.
deliveryStreamDescription_destinations :: Lens.Lens' DeliveryStreamDescription [DestinationDescription]
deliveryStreamDescription_destinations :: Lens' DeliveryStreamDescription [DestinationDescription]
deliveryStreamDescription_destinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamDescription' {[DestinationDescription]
destinations :: [DestinationDescription]
$sel:destinations:DeliveryStreamDescription' :: DeliveryStreamDescription -> [DestinationDescription]
destinations} -> [DestinationDescription]
destinations) (\s :: DeliveryStreamDescription
s@DeliveryStreamDescription' {} [DestinationDescription]
a -> DeliveryStreamDescription
s {$sel:destinations:DeliveryStreamDescription' :: [DestinationDescription]
destinations = [DestinationDescription]
a} :: DeliveryStreamDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Indicates whether there are more destinations available to list.
deliveryStreamDescription_hasMoreDestinations :: Lens.Lens' DeliveryStreamDescription Prelude.Bool
deliveryStreamDescription_hasMoreDestinations :: Lens' DeliveryStreamDescription Bool
deliveryStreamDescription_hasMoreDestinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliveryStreamDescription' {Bool
hasMoreDestinations :: Bool
$sel:hasMoreDestinations:DeliveryStreamDescription' :: DeliveryStreamDescription -> Bool
hasMoreDestinations} -> Bool
hasMoreDestinations) (\s :: DeliveryStreamDescription
s@DeliveryStreamDescription' {} Bool
a -> DeliveryStreamDescription
s {$sel:hasMoreDestinations:DeliveryStreamDescription' :: Bool
hasMoreDestinations = Bool
a} :: DeliveryStreamDescription)

instance Data.FromJSON DeliveryStreamDescription where
  parseJSON :: Value -> Parser DeliveryStreamDescription
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DeliveryStreamDescription"
      ( \Object
x ->
          Maybe POSIX
-> Maybe DeliveryStreamEncryptionConfiguration
-> Maybe FailureDescription
-> Maybe POSIX
-> Maybe SourceDescription
-> Text
-> Text
-> DeliveryStreamStatus
-> DeliveryStreamType
-> Text
-> [DestinationDescription]
-> Bool
-> DeliveryStreamDescription
DeliveryStreamDescription'
            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
"CreateTimestamp")
            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
"DeliveryStreamEncryptionConfiguration")
            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
"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
"LastUpdateTimestamp")
            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
"Source")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"DeliveryStreamName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"DeliveryStreamARN")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"DeliveryStreamStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"DeliveryStreamType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"VersionId")
            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
"Destinations" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"HasMoreDestinations")
      )

instance Prelude.Hashable DeliveryStreamDescription where
  hashWithSalt :: Int -> DeliveryStreamDescription -> Int
hashWithSalt Int
_salt DeliveryStreamDescription' {Bool
[DestinationDescription]
Maybe POSIX
Maybe FailureDescription
Maybe DeliveryStreamEncryptionConfiguration
Maybe SourceDescription
Text
DeliveryStreamStatus
DeliveryStreamType
hasMoreDestinations :: Bool
destinations :: [DestinationDescription]
versionId :: Text
deliveryStreamType :: DeliveryStreamType
deliveryStreamStatus :: DeliveryStreamStatus
deliveryStreamARN :: Text
deliveryStreamName :: Text
source :: Maybe SourceDescription
lastUpdateTimestamp :: Maybe POSIX
failureDescription :: Maybe FailureDescription
deliveryStreamEncryptionConfiguration :: Maybe DeliveryStreamEncryptionConfiguration
createTimestamp :: Maybe POSIX
$sel:hasMoreDestinations:DeliveryStreamDescription' :: DeliveryStreamDescription -> Bool
$sel:destinations:DeliveryStreamDescription' :: DeliveryStreamDescription -> [DestinationDescription]
$sel:versionId:DeliveryStreamDescription' :: DeliveryStreamDescription -> Text
$sel:deliveryStreamType:DeliveryStreamDescription' :: DeliveryStreamDescription -> DeliveryStreamType
$sel:deliveryStreamStatus:DeliveryStreamDescription' :: DeliveryStreamDescription -> DeliveryStreamStatus
$sel:deliveryStreamARN:DeliveryStreamDescription' :: DeliveryStreamDescription -> Text
$sel:deliveryStreamName:DeliveryStreamDescription' :: DeliveryStreamDescription -> Text
$sel:source:DeliveryStreamDescription' :: DeliveryStreamDescription -> Maybe SourceDescription
$sel:lastUpdateTimestamp:DeliveryStreamDescription' :: DeliveryStreamDescription -> Maybe POSIX
$sel:failureDescription:DeliveryStreamDescription' :: DeliveryStreamDescription -> Maybe FailureDescription
$sel:deliveryStreamEncryptionConfiguration:DeliveryStreamDescription' :: DeliveryStreamDescription
-> Maybe DeliveryStreamEncryptionConfiguration
$sel:createTimestamp:DeliveryStreamDescription' :: DeliveryStreamDescription -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeliveryStreamEncryptionConfiguration
deliveryStreamEncryptionConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FailureDescription
failureDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastUpdateTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SourceDescription
source
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deliveryStreamName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deliveryStreamARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DeliveryStreamStatus
deliveryStreamStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DeliveryStreamType
deliveryStreamType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
versionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [DestinationDescription]
destinations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Bool
hasMoreDestinations

instance Prelude.NFData DeliveryStreamDescription where
  rnf :: DeliveryStreamDescription -> ()
rnf DeliveryStreamDescription' {Bool
[DestinationDescription]
Maybe POSIX
Maybe FailureDescription
Maybe DeliveryStreamEncryptionConfiguration
Maybe SourceDescription
Text
DeliveryStreamStatus
DeliveryStreamType
hasMoreDestinations :: Bool
destinations :: [DestinationDescription]
versionId :: Text
deliveryStreamType :: DeliveryStreamType
deliveryStreamStatus :: DeliveryStreamStatus
deliveryStreamARN :: Text
deliveryStreamName :: Text
source :: Maybe SourceDescription
lastUpdateTimestamp :: Maybe POSIX
failureDescription :: Maybe FailureDescription
deliveryStreamEncryptionConfiguration :: Maybe DeliveryStreamEncryptionConfiguration
createTimestamp :: Maybe POSIX
$sel:hasMoreDestinations:DeliveryStreamDescription' :: DeliveryStreamDescription -> Bool
$sel:destinations:DeliveryStreamDescription' :: DeliveryStreamDescription -> [DestinationDescription]
$sel:versionId:DeliveryStreamDescription' :: DeliveryStreamDescription -> Text
$sel:deliveryStreamType:DeliveryStreamDescription' :: DeliveryStreamDescription -> DeliveryStreamType
$sel:deliveryStreamStatus:DeliveryStreamDescription' :: DeliveryStreamDescription -> DeliveryStreamStatus
$sel:deliveryStreamARN:DeliveryStreamDescription' :: DeliveryStreamDescription -> Text
$sel:deliveryStreamName:DeliveryStreamDescription' :: DeliveryStreamDescription -> Text
$sel:source:DeliveryStreamDescription' :: DeliveryStreamDescription -> Maybe SourceDescription
$sel:lastUpdateTimestamp:DeliveryStreamDescription' :: DeliveryStreamDescription -> Maybe POSIX
$sel:failureDescription:DeliveryStreamDescription' :: DeliveryStreamDescription -> Maybe FailureDescription
$sel:deliveryStreamEncryptionConfiguration:DeliveryStreamDescription' :: DeliveryStreamDescription
-> Maybe DeliveryStreamEncryptionConfiguration
$sel:createTimestamp:DeliveryStreamDescription' :: DeliveryStreamDescription -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeliveryStreamEncryptionConfiguration
deliveryStreamEncryptionConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 POSIX
lastUpdateTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SourceDescription
source
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
deliveryStreamName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
deliveryStreamARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DeliveryStreamStatus
deliveryStreamStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DeliveryStreamType
deliveryStreamType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
versionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [DestinationDescription]
destinations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Bool
hasMoreDestinations