{-# 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.Config.Types.ConfigStreamDeliveryInfo
-- 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.Config.Types.ConfigStreamDeliveryInfo where

import Amazonka.Config.Types.DeliveryStatus
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

-- | A list that contains the status of the delivery of the configuration
-- stream notification to the Amazon SNS topic.
--
-- /See:/ 'newConfigStreamDeliveryInfo' smart constructor.
data ConfigStreamDeliveryInfo = ConfigStreamDeliveryInfo'
  { -- | The error code from the last attempted delivery.
    ConfigStreamDeliveryInfo -> Maybe Text
lastErrorCode :: Prelude.Maybe Prelude.Text,
    -- | The error message from the last attempted delivery.
    ConfigStreamDeliveryInfo -> Maybe Text
lastErrorMessage :: Prelude.Maybe Prelude.Text,
    -- | Status of the last attempted delivery.
    --
    -- __Note__ Providing an SNS topic on a
    -- <https://docs.aws.amazon.com/config/latest/APIReference/API_DeliveryChannel.html DeliveryChannel>
    -- for Config is optional. If the SNS delivery is turned off, the last
    -- status will be __Not_Applicable__.
    ConfigStreamDeliveryInfo -> Maybe DeliveryStatus
lastStatus :: Prelude.Maybe DeliveryStatus,
    -- | The time from the last status change.
    ConfigStreamDeliveryInfo -> Maybe POSIX
lastStatusChangeTime :: Prelude.Maybe Data.POSIX
  }
  deriving (ConfigStreamDeliveryInfo -> ConfigStreamDeliveryInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfigStreamDeliveryInfo -> ConfigStreamDeliveryInfo -> Bool
$c/= :: ConfigStreamDeliveryInfo -> ConfigStreamDeliveryInfo -> Bool
== :: ConfigStreamDeliveryInfo -> ConfigStreamDeliveryInfo -> Bool
$c== :: ConfigStreamDeliveryInfo -> ConfigStreamDeliveryInfo -> Bool
Prelude.Eq, ReadPrec [ConfigStreamDeliveryInfo]
ReadPrec ConfigStreamDeliveryInfo
Int -> ReadS ConfigStreamDeliveryInfo
ReadS [ConfigStreamDeliveryInfo]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConfigStreamDeliveryInfo]
$creadListPrec :: ReadPrec [ConfigStreamDeliveryInfo]
readPrec :: ReadPrec ConfigStreamDeliveryInfo
$creadPrec :: ReadPrec ConfigStreamDeliveryInfo
readList :: ReadS [ConfigStreamDeliveryInfo]
$creadList :: ReadS [ConfigStreamDeliveryInfo]
readsPrec :: Int -> ReadS ConfigStreamDeliveryInfo
$creadsPrec :: Int -> ReadS ConfigStreamDeliveryInfo
Prelude.Read, Int -> ConfigStreamDeliveryInfo -> ShowS
[ConfigStreamDeliveryInfo] -> ShowS
ConfigStreamDeliveryInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfigStreamDeliveryInfo] -> ShowS
$cshowList :: [ConfigStreamDeliveryInfo] -> ShowS
show :: ConfigStreamDeliveryInfo -> String
$cshow :: ConfigStreamDeliveryInfo -> String
showsPrec :: Int -> ConfigStreamDeliveryInfo -> ShowS
$cshowsPrec :: Int -> ConfigStreamDeliveryInfo -> ShowS
Prelude.Show, forall x.
Rep ConfigStreamDeliveryInfo x -> ConfigStreamDeliveryInfo
forall x.
ConfigStreamDeliveryInfo -> Rep ConfigStreamDeliveryInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ConfigStreamDeliveryInfo x -> ConfigStreamDeliveryInfo
$cfrom :: forall x.
ConfigStreamDeliveryInfo -> Rep ConfigStreamDeliveryInfo x
Prelude.Generic)

-- |
-- Create a value of 'ConfigStreamDeliveryInfo' 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:
--
-- 'lastErrorCode', 'configStreamDeliveryInfo_lastErrorCode' - The error code from the last attempted delivery.
--
-- 'lastErrorMessage', 'configStreamDeliveryInfo_lastErrorMessage' - The error message from the last attempted delivery.
--
-- 'lastStatus', 'configStreamDeliveryInfo_lastStatus' - Status of the last attempted delivery.
--
-- __Note__ Providing an SNS topic on a
-- <https://docs.aws.amazon.com/config/latest/APIReference/API_DeliveryChannel.html DeliveryChannel>
-- for Config is optional. If the SNS delivery is turned off, the last
-- status will be __Not_Applicable__.
--
-- 'lastStatusChangeTime', 'configStreamDeliveryInfo_lastStatusChangeTime' - The time from the last status change.
newConfigStreamDeliveryInfo ::
  ConfigStreamDeliveryInfo
newConfigStreamDeliveryInfo :: ConfigStreamDeliveryInfo
newConfigStreamDeliveryInfo =
  ConfigStreamDeliveryInfo'
    { $sel:lastErrorCode:ConfigStreamDeliveryInfo' :: Maybe Text
lastErrorCode =
        forall a. Maybe a
Prelude.Nothing,
      $sel:lastErrorMessage:ConfigStreamDeliveryInfo' :: Maybe Text
lastErrorMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:lastStatus:ConfigStreamDeliveryInfo' :: Maybe DeliveryStatus
lastStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:lastStatusChangeTime:ConfigStreamDeliveryInfo' :: Maybe POSIX
lastStatusChangeTime = forall a. Maybe a
Prelude.Nothing
    }

-- | The error code from the last attempted delivery.
configStreamDeliveryInfo_lastErrorCode :: Lens.Lens' ConfigStreamDeliveryInfo (Prelude.Maybe Prelude.Text)
configStreamDeliveryInfo_lastErrorCode :: Lens' ConfigStreamDeliveryInfo (Maybe Text)
configStreamDeliveryInfo_lastErrorCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfigStreamDeliveryInfo' {Maybe Text
lastErrorCode :: Maybe Text
$sel:lastErrorCode:ConfigStreamDeliveryInfo' :: ConfigStreamDeliveryInfo -> Maybe Text
lastErrorCode} -> Maybe Text
lastErrorCode) (\s :: ConfigStreamDeliveryInfo
s@ConfigStreamDeliveryInfo' {} Maybe Text
a -> ConfigStreamDeliveryInfo
s {$sel:lastErrorCode:ConfigStreamDeliveryInfo' :: Maybe Text
lastErrorCode = Maybe Text
a} :: ConfigStreamDeliveryInfo)

-- | The error message from the last attempted delivery.
configStreamDeliveryInfo_lastErrorMessage :: Lens.Lens' ConfigStreamDeliveryInfo (Prelude.Maybe Prelude.Text)
configStreamDeliveryInfo_lastErrorMessage :: Lens' ConfigStreamDeliveryInfo (Maybe Text)
configStreamDeliveryInfo_lastErrorMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfigStreamDeliveryInfo' {Maybe Text
lastErrorMessage :: Maybe Text
$sel:lastErrorMessage:ConfigStreamDeliveryInfo' :: ConfigStreamDeliveryInfo -> Maybe Text
lastErrorMessage} -> Maybe Text
lastErrorMessage) (\s :: ConfigStreamDeliveryInfo
s@ConfigStreamDeliveryInfo' {} Maybe Text
a -> ConfigStreamDeliveryInfo
s {$sel:lastErrorMessage:ConfigStreamDeliveryInfo' :: Maybe Text
lastErrorMessage = Maybe Text
a} :: ConfigStreamDeliveryInfo)

-- | Status of the last attempted delivery.
--
-- __Note__ Providing an SNS topic on a
-- <https://docs.aws.amazon.com/config/latest/APIReference/API_DeliveryChannel.html DeliveryChannel>
-- for Config is optional. If the SNS delivery is turned off, the last
-- status will be __Not_Applicable__.
configStreamDeliveryInfo_lastStatus :: Lens.Lens' ConfigStreamDeliveryInfo (Prelude.Maybe DeliveryStatus)
configStreamDeliveryInfo_lastStatus :: Lens' ConfigStreamDeliveryInfo (Maybe DeliveryStatus)
configStreamDeliveryInfo_lastStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfigStreamDeliveryInfo' {Maybe DeliveryStatus
lastStatus :: Maybe DeliveryStatus
$sel:lastStatus:ConfigStreamDeliveryInfo' :: ConfigStreamDeliveryInfo -> Maybe DeliveryStatus
lastStatus} -> Maybe DeliveryStatus
lastStatus) (\s :: ConfigStreamDeliveryInfo
s@ConfigStreamDeliveryInfo' {} Maybe DeliveryStatus
a -> ConfigStreamDeliveryInfo
s {$sel:lastStatus:ConfigStreamDeliveryInfo' :: Maybe DeliveryStatus
lastStatus = Maybe DeliveryStatus
a} :: ConfigStreamDeliveryInfo)

-- | The time from the last status change.
configStreamDeliveryInfo_lastStatusChangeTime :: Lens.Lens' ConfigStreamDeliveryInfo (Prelude.Maybe Prelude.UTCTime)
configStreamDeliveryInfo_lastStatusChangeTime :: Lens' ConfigStreamDeliveryInfo (Maybe UTCTime)
configStreamDeliveryInfo_lastStatusChangeTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConfigStreamDeliveryInfo' {Maybe POSIX
lastStatusChangeTime :: Maybe POSIX
$sel:lastStatusChangeTime:ConfigStreamDeliveryInfo' :: ConfigStreamDeliveryInfo -> Maybe POSIX
lastStatusChangeTime} -> Maybe POSIX
lastStatusChangeTime) (\s :: ConfigStreamDeliveryInfo
s@ConfigStreamDeliveryInfo' {} Maybe POSIX
a -> ConfigStreamDeliveryInfo
s {$sel:lastStatusChangeTime:ConfigStreamDeliveryInfo' :: Maybe POSIX
lastStatusChangeTime = Maybe POSIX
a} :: ConfigStreamDeliveryInfo) 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

instance Data.FromJSON ConfigStreamDeliveryInfo where
  parseJSON :: Value -> Parser ConfigStreamDeliveryInfo
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ConfigStreamDeliveryInfo"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe DeliveryStatus
-> Maybe POSIX
-> ConfigStreamDeliveryInfo
ConfigStreamDeliveryInfo'
            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
"lastErrorCode")
            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
"lastErrorMessage")
            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
"lastStatus")
            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
"lastStatusChangeTime")
      )

instance Prelude.Hashable ConfigStreamDeliveryInfo where
  hashWithSalt :: Int -> ConfigStreamDeliveryInfo -> Int
hashWithSalt Int
_salt ConfigStreamDeliveryInfo' {Maybe Text
Maybe POSIX
Maybe DeliveryStatus
lastStatusChangeTime :: Maybe POSIX
lastStatus :: Maybe DeliveryStatus
lastErrorMessage :: Maybe Text
lastErrorCode :: Maybe Text
$sel:lastStatusChangeTime:ConfigStreamDeliveryInfo' :: ConfigStreamDeliveryInfo -> Maybe POSIX
$sel:lastStatus:ConfigStreamDeliveryInfo' :: ConfigStreamDeliveryInfo -> Maybe DeliveryStatus
$sel:lastErrorMessage:ConfigStreamDeliveryInfo' :: ConfigStreamDeliveryInfo -> Maybe Text
$sel:lastErrorCode:ConfigStreamDeliveryInfo' :: ConfigStreamDeliveryInfo -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
lastErrorCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
lastErrorMessage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeliveryStatus
lastStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastStatusChangeTime

instance Prelude.NFData ConfigStreamDeliveryInfo where
  rnf :: ConfigStreamDeliveryInfo -> ()
rnf ConfigStreamDeliveryInfo' {Maybe Text
Maybe POSIX
Maybe DeliveryStatus
lastStatusChangeTime :: Maybe POSIX
lastStatus :: Maybe DeliveryStatus
lastErrorMessage :: Maybe Text
lastErrorCode :: Maybe Text
$sel:lastStatusChangeTime:ConfigStreamDeliveryInfo' :: ConfigStreamDeliveryInfo -> Maybe POSIX
$sel:lastStatus:ConfigStreamDeliveryInfo' :: ConfigStreamDeliveryInfo -> Maybe DeliveryStatus
$sel:lastErrorMessage:ConfigStreamDeliveryInfo' :: ConfigStreamDeliveryInfo -> Maybe Text
$sel:lastErrorCode:ConfigStreamDeliveryInfo' :: ConfigStreamDeliveryInfo -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastErrorCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastErrorMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeliveryStatus
lastStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastStatusChangeTime