{-# 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.ElastiCache.Types.LogDeliveryConfiguration
-- 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.ElastiCache.Types.LogDeliveryConfiguration where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ElastiCache.Types.DestinationDetails
import Amazonka.ElastiCache.Types.DestinationType
import Amazonka.ElastiCache.Types.LogDeliveryConfigurationStatus
import Amazonka.ElastiCache.Types.LogFormat
import Amazonka.ElastiCache.Types.LogType
import qualified Amazonka.Prelude as Prelude

-- | Returns the destination, format and type of the logs.
--
-- /See:/ 'newLogDeliveryConfiguration' smart constructor.
data LogDeliveryConfiguration = LogDeliveryConfiguration'
  { -- | Configuration details of either a CloudWatch Logs destination or Kinesis
    -- Data Firehose destination.
    LogDeliveryConfiguration -> Maybe DestinationDetails
destinationDetails :: Prelude.Maybe DestinationDetails,
    -- | Returns the destination type, either @cloudwatch-logs@ or
    -- @kinesis-firehose@.
    LogDeliveryConfiguration -> Maybe DestinationType
destinationType :: Prelude.Maybe DestinationType,
    -- | Returns the log format, either JSON or TEXT.
    LogDeliveryConfiguration -> Maybe LogFormat
logFormat :: Prelude.Maybe LogFormat,
    -- | Refers to <https://redis.io/commands/slowlog slow-log> or engine-log.
    LogDeliveryConfiguration -> Maybe LogType
logType :: Prelude.Maybe LogType,
    -- | Returns an error message for the log delivery configuration.
    LogDeliveryConfiguration -> Maybe Text
message :: Prelude.Maybe Prelude.Text,
    -- | Returns the log delivery configuration status. Values are one of
    -- @enabling@ | @disabling@ | @modifying@ | @active@ | @error@
    LogDeliveryConfiguration -> Maybe LogDeliveryConfigurationStatus
status :: Prelude.Maybe LogDeliveryConfigurationStatus
  }
  deriving (LogDeliveryConfiguration -> LogDeliveryConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogDeliveryConfiguration -> LogDeliveryConfiguration -> Bool
$c/= :: LogDeliveryConfiguration -> LogDeliveryConfiguration -> Bool
== :: LogDeliveryConfiguration -> LogDeliveryConfiguration -> Bool
$c== :: LogDeliveryConfiguration -> LogDeliveryConfiguration -> Bool
Prelude.Eq, ReadPrec [LogDeliveryConfiguration]
ReadPrec LogDeliveryConfiguration
Int -> ReadS LogDeliveryConfiguration
ReadS [LogDeliveryConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LogDeliveryConfiguration]
$creadListPrec :: ReadPrec [LogDeliveryConfiguration]
readPrec :: ReadPrec LogDeliveryConfiguration
$creadPrec :: ReadPrec LogDeliveryConfiguration
readList :: ReadS [LogDeliveryConfiguration]
$creadList :: ReadS [LogDeliveryConfiguration]
readsPrec :: Int -> ReadS LogDeliveryConfiguration
$creadsPrec :: Int -> ReadS LogDeliveryConfiguration
Prelude.Read, Int -> LogDeliveryConfiguration -> ShowS
[LogDeliveryConfiguration] -> ShowS
LogDeliveryConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogDeliveryConfiguration] -> ShowS
$cshowList :: [LogDeliveryConfiguration] -> ShowS
show :: LogDeliveryConfiguration -> String
$cshow :: LogDeliveryConfiguration -> String
showsPrec :: Int -> LogDeliveryConfiguration -> ShowS
$cshowsPrec :: Int -> LogDeliveryConfiguration -> ShowS
Prelude.Show, forall x.
Rep LogDeliveryConfiguration x -> LogDeliveryConfiguration
forall x.
LogDeliveryConfiguration -> Rep LogDeliveryConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep LogDeliveryConfiguration x -> LogDeliveryConfiguration
$cfrom :: forall x.
LogDeliveryConfiguration -> Rep LogDeliveryConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'LogDeliveryConfiguration' 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:
--
-- 'destinationDetails', 'logDeliveryConfiguration_destinationDetails' - Configuration details of either a CloudWatch Logs destination or Kinesis
-- Data Firehose destination.
--
-- 'destinationType', 'logDeliveryConfiguration_destinationType' - Returns the destination type, either @cloudwatch-logs@ or
-- @kinesis-firehose@.
--
-- 'logFormat', 'logDeliveryConfiguration_logFormat' - Returns the log format, either JSON or TEXT.
--
-- 'logType', 'logDeliveryConfiguration_logType' - Refers to <https://redis.io/commands/slowlog slow-log> or engine-log.
--
-- 'message', 'logDeliveryConfiguration_message' - Returns an error message for the log delivery configuration.
--
-- 'status', 'logDeliveryConfiguration_status' - Returns the log delivery configuration status. Values are one of
-- @enabling@ | @disabling@ | @modifying@ | @active@ | @error@
newLogDeliveryConfiguration ::
  LogDeliveryConfiguration
newLogDeliveryConfiguration :: LogDeliveryConfiguration
newLogDeliveryConfiguration =
  LogDeliveryConfiguration'
    { $sel:destinationDetails:LogDeliveryConfiguration' :: Maybe DestinationDetails
destinationDetails =
        forall a. Maybe a
Prelude.Nothing,
      $sel:destinationType:LogDeliveryConfiguration' :: Maybe DestinationType
destinationType = forall a. Maybe a
Prelude.Nothing,
      $sel:logFormat:LogDeliveryConfiguration' :: Maybe LogFormat
logFormat = forall a. Maybe a
Prelude.Nothing,
      $sel:logType:LogDeliveryConfiguration' :: Maybe LogType
logType = forall a. Maybe a
Prelude.Nothing,
      $sel:message:LogDeliveryConfiguration' :: Maybe Text
message = forall a. Maybe a
Prelude.Nothing,
      $sel:status:LogDeliveryConfiguration' :: Maybe LogDeliveryConfigurationStatus
status = forall a. Maybe a
Prelude.Nothing
    }

-- | Configuration details of either a CloudWatch Logs destination or Kinesis
-- Data Firehose destination.
logDeliveryConfiguration_destinationDetails :: Lens.Lens' LogDeliveryConfiguration (Prelude.Maybe DestinationDetails)
logDeliveryConfiguration_destinationDetails :: Lens' LogDeliveryConfiguration (Maybe DestinationDetails)
logDeliveryConfiguration_destinationDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogDeliveryConfiguration' {Maybe DestinationDetails
destinationDetails :: Maybe DestinationDetails
$sel:destinationDetails:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe DestinationDetails
destinationDetails} -> Maybe DestinationDetails
destinationDetails) (\s :: LogDeliveryConfiguration
s@LogDeliveryConfiguration' {} Maybe DestinationDetails
a -> LogDeliveryConfiguration
s {$sel:destinationDetails:LogDeliveryConfiguration' :: Maybe DestinationDetails
destinationDetails = Maybe DestinationDetails
a} :: LogDeliveryConfiguration)

-- | Returns the destination type, either @cloudwatch-logs@ or
-- @kinesis-firehose@.
logDeliveryConfiguration_destinationType :: Lens.Lens' LogDeliveryConfiguration (Prelude.Maybe DestinationType)
logDeliveryConfiguration_destinationType :: Lens' LogDeliveryConfiguration (Maybe DestinationType)
logDeliveryConfiguration_destinationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogDeliveryConfiguration' {Maybe DestinationType
destinationType :: Maybe DestinationType
$sel:destinationType:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe DestinationType
destinationType} -> Maybe DestinationType
destinationType) (\s :: LogDeliveryConfiguration
s@LogDeliveryConfiguration' {} Maybe DestinationType
a -> LogDeliveryConfiguration
s {$sel:destinationType:LogDeliveryConfiguration' :: Maybe DestinationType
destinationType = Maybe DestinationType
a} :: LogDeliveryConfiguration)

-- | Returns the log format, either JSON or TEXT.
logDeliveryConfiguration_logFormat :: Lens.Lens' LogDeliveryConfiguration (Prelude.Maybe LogFormat)
logDeliveryConfiguration_logFormat :: Lens' LogDeliveryConfiguration (Maybe LogFormat)
logDeliveryConfiguration_logFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogDeliveryConfiguration' {Maybe LogFormat
logFormat :: Maybe LogFormat
$sel:logFormat:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe LogFormat
logFormat} -> Maybe LogFormat
logFormat) (\s :: LogDeliveryConfiguration
s@LogDeliveryConfiguration' {} Maybe LogFormat
a -> LogDeliveryConfiguration
s {$sel:logFormat:LogDeliveryConfiguration' :: Maybe LogFormat
logFormat = Maybe LogFormat
a} :: LogDeliveryConfiguration)

-- | Refers to <https://redis.io/commands/slowlog slow-log> or engine-log.
logDeliveryConfiguration_logType :: Lens.Lens' LogDeliveryConfiguration (Prelude.Maybe LogType)
logDeliveryConfiguration_logType :: Lens' LogDeliveryConfiguration (Maybe LogType)
logDeliveryConfiguration_logType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogDeliveryConfiguration' {Maybe LogType
logType :: Maybe LogType
$sel:logType:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe LogType
logType} -> Maybe LogType
logType) (\s :: LogDeliveryConfiguration
s@LogDeliveryConfiguration' {} Maybe LogType
a -> LogDeliveryConfiguration
s {$sel:logType:LogDeliveryConfiguration' :: Maybe LogType
logType = Maybe LogType
a} :: LogDeliveryConfiguration)

-- | Returns an error message for the log delivery configuration.
logDeliveryConfiguration_message :: Lens.Lens' LogDeliveryConfiguration (Prelude.Maybe Prelude.Text)
logDeliveryConfiguration_message :: Lens' LogDeliveryConfiguration (Maybe Text)
logDeliveryConfiguration_message = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogDeliveryConfiguration' {Maybe Text
message :: Maybe Text
$sel:message:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe Text
message} -> Maybe Text
message) (\s :: LogDeliveryConfiguration
s@LogDeliveryConfiguration' {} Maybe Text
a -> LogDeliveryConfiguration
s {$sel:message:LogDeliveryConfiguration' :: Maybe Text
message = Maybe Text
a} :: LogDeliveryConfiguration)

-- | Returns the log delivery configuration status. Values are one of
-- @enabling@ | @disabling@ | @modifying@ | @active@ | @error@
logDeliveryConfiguration_status :: Lens.Lens' LogDeliveryConfiguration (Prelude.Maybe LogDeliveryConfigurationStatus)
logDeliveryConfiguration_status :: Lens'
  LogDeliveryConfiguration (Maybe LogDeliveryConfigurationStatus)
logDeliveryConfiguration_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LogDeliveryConfiguration' {Maybe LogDeliveryConfigurationStatus
status :: Maybe LogDeliveryConfigurationStatus
$sel:status:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe LogDeliveryConfigurationStatus
status} -> Maybe LogDeliveryConfigurationStatus
status) (\s :: LogDeliveryConfiguration
s@LogDeliveryConfiguration' {} Maybe LogDeliveryConfigurationStatus
a -> LogDeliveryConfiguration
s {$sel:status:LogDeliveryConfiguration' :: Maybe LogDeliveryConfigurationStatus
status = Maybe LogDeliveryConfigurationStatus
a} :: LogDeliveryConfiguration)

instance Data.FromXML LogDeliveryConfiguration where
  parseXML :: [Node] -> Either String LogDeliveryConfiguration
parseXML [Node]
x =
    Maybe DestinationDetails
-> Maybe DestinationType
-> Maybe LogFormat
-> Maybe LogType
-> Maybe Text
-> Maybe LogDeliveryConfigurationStatus
-> LogDeliveryConfiguration
LogDeliveryConfiguration'
      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
"DestinationDetails")
      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
"DestinationType")
      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
"LogFormat")
      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
"LogType")
      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
"Message")
      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
"Status")

instance Prelude.Hashable LogDeliveryConfiguration where
  hashWithSalt :: Int -> LogDeliveryConfiguration -> Int
hashWithSalt Int
_salt LogDeliveryConfiguration' {Maybe Text
Maybe DestinationType
Maybe DestinationDetails
Maybe LogDeliveryConfigurationStatus
Maybe LogFormat
Maybe LogType
status :: Maybe LogDeliveryConfigurationStatus
message :: Maybe Text
logType :: Maybe LogType
logFormat :: Maybe LogFormat
destinationType :: Maybe DestinationType
destinationDetails :: Maybe DestinationDetails
$sel:status:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe LogDeliveryConfigurationStatus
$sel:message:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe Text
$sel:logType:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe LogType
$sel:logFormat:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe LogFormat
$sel:destinationType:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe DestinationType
$sel:destinationDetails:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe DestinationDetails
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DestinationDetails
destinationDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DestinationType
destinationType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogFormat
logFormat
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogType
logType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
message
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogDeliveryConfigurationStatus
status

instance Prelude.NFData LogDeliveryConfiguration where
  rnf :: LogDeliveryConfiguration -> ()
rnf LogDeliveryConfiguration' {Maybe Text
Maybe DestinationType
Maybe DestinationDetails
Maybe LogDeliveryConfigurationStatus
Maybe LogFormat
Maybe LogType
status :: Maybe LogDeliveryConfigurationStatus
message :: Maybe Text
logType :: Maybe LogType
logFormat :: Maybe LogFormat
destinationType :: Maybe DestinationType
destinationDetails :: Maybe DestinationDetails
$sel:status:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe LogDeliveryConfigurationStatus
$sel:message:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe Text
$sel:logType:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe LogType
$sel:logFormat:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe LogFormat
$sel:destinationType:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe DestinationType
$sel:destinationDetails:LogDeliveryConfiguration' :: LogDeliveryConfiguration -> Maybe DestinationDetails
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DestinationDetails
destinationDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DestinationType
destinationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogFormat
logFormat
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogType
logType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
message
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogDeliveryConfigurationStatus
status