{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

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

-- |
-- Module      : Amazonka.CloudFront.UpdateRealtimeLogConfig
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates a real-time log configuration.
--
-- When you update a real-time log configuration, all the parameters are
-- updated with the values provided in the request. You cannot update some
-- parameters independent of others. To update a real-time log
-- configuration:
--
-- 1.  Call @GetRealtimeLogConfig@ to get the current real-time log
--     configuration.
--
-- 2.  Locally modify the parameters in the real-time log configuration
--     that you want to update.
--
-- 3.  Call this API (@UpdateRealtimeLogConfig@) by providing the entire
--     real-time log configuration, including the parameters that you
--     modified and those that you didn\'t.
--
-- You cannot update a real-time log configuration\'s @Name@ or @ARN@.
module Amazonka.CloudFront.UpdateRealtimeLogConfig
  ( -- * Creating a Request
    UpdateRealtimeLogConfig (..),
    newUpdateRealtimeLogConfig,

    -- * Request Lenses
    updateRealtimeLogConfig_arn,
    updateRealtimeLogConfig_endPoints,
    updateRealtimeLogConfig_fields,
    updateRealtimeLogConfig_name,
    updateRealtimeLogConfig_samplingRate,

    -- * Destructuring the Response
    UpdateRealtimeLogConfigResponse (..),
    newUpdateRealtimeLogConfigResponse,

    -- * Response Lenses
    updateRealtimeLogConfigResponse_realtimeLogConfig,
    updateRealtimeLogConfigResponse_httpStatus,
  )
where

import Amazonka.CloudFront.Types
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
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateRealtimeLogConfig' smart constructor.
data UpdateRealtimeLogConfig = UpdateRealtimeLogConfig'
  { -- | The Amazon Resource Name (ARN) for this real-time log configuration.
    UpdateRealtimeLogConfig -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | Contains information about the Amazon Kinesis data stream where you are
    -- sending real-time log data.
    UpdateRealtimeLogConfig -> Maybe [EndPoint]
endPoints :: Prelude.Maybe [EndPoint],
    -- | A list of fields to include in each real-time log record.
    --
    -- For more information about fields, see
    -- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/real-time-logs.html#understand-real-time-log-config-fields Real-time log configuration fields>
    -- in the /Amazon CloudFront Developer Guide/.
    UpdateRealtimeLogConfig -> Maybe [Text]
fields :: Prelude.Maybe [Prelude.Text],
    -- | The name for this real-time log configuration.
    UpdateRealtimeLogConfig -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The sampling rate for this real-time log configuration. The sampling
    -- rate determines the percentage of viewer requests that are represented
    -- in the real-time log data. You must provide an integer between 1 and
    -- 100, inclusive.
    UpdateRealtimeLogConfig -> Maybe Integer
samplingRate :: Prelude.Maybe Prelude.Integer
  }
  deriving (UpdateRealtimeLogConfig -> UpdateRealtimeLogConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRealtimeLogConfig -> UpdateRealtimeLogConfig -> Bool
$c/= :: UpdateRealtimeLogConfig -> UpdateRealtimeLogConfig -> Bool
== :: UpdateRealtimeLogConfig -> UpdateRealtimeLogConfig -> Bool
$c== :: UpdateRealtimeLogConfig -> UpdateRealtimeLogConfig -> Bool
Prelude.Eq, ReadPrec [UpdateRealtimeLogConfig]
ReadPrec UpdateRealtimeLogConfig
Int -> ReadS UpdateRealtimeLogConfig
ReadS [UpdateRealtimeLogConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRealtimeLogConfig]
$creadListPrec :: ReadPrec [UpdateRealtimeLogConfig]
readPrec :: ReadPrec UpdateRealtimeLogConfig
$creadPrec :: ReadPrec UpdateRealtimeLogConfig
readList :: ReadS [UpdateRealtimeLogConfig]
$creadList :: ReadS [UpdateRealtimeLogConfig]
readsPrec :: Int -> ReadS UpdateRealtimeLogConfig
$creadsPrec :: Int -> ReadS UpdateRealtimeLogConfig
Prelude.Read, Int -> UpdateRealtimeLogConfig -> ShowS
[UpdateRealtimeLogConfig] -> ShowS
UpdateRealtimeLogConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRealtimeLogConfig] -> ShowS
$cshowList :: [UpdateRealtimeLogConfig] -> ShowS
show :: UpdateRealtimeLogConfig -> String
$cshow :: UpdateRealtimeLogConfig -> String
showsPrec :: Int -> UpdateRealtimeLogConfig -> ShowS
$cshowsPrec :: Int -> UpdateRealtimeLogConfig -> ShowS
Prelude.Show, forall x. Rep UpdateRealtimeLogConfig x -> UpdateRealtimeLogConfig
forall x. UpdateRealtimeLogConfig -> Rep UpdateRealtimeLogConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRealtimeLogConfig x -> UpdateRealtimeLogConfig
$cfrom :: forall x. UpdateRealtimeLogConfig -> Rep UpdateRealtimeLogConfig x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRealtimeLogConfig' 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:
--
-- 'arn', 'updateRealtimeLogConfig_arn' - The Amazon Resource Name (ARN) for this real-time log configuration.
--
-- 'endPoints', 'updateRealtimeLogConfig_endPoints' - Contains information about the Amazon Kinesis data stream where you are
-- sending real-time log data.
--
-- 'fields', 'updateRealtimeLogConfig_fields' - A list of fields to include in each real-time log record.
--
-- For more information about fields, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/real-time-logs.html#understand-real-time-log-config-fields Real-time log configuration fields>
-- in the /Amazon CloudFront Developer Guide/.
--
-- 'name', 'updateRealtimeLogConfig_name' - The name for this real-time log configuration.
--
-- 'samplingRate', 'updateRealtimeLogConfig_samplingRate' - The sampling rate for this real-time log configuration. The sampling
-- rate determines the percentage of viewer requests that are represented
-- in the real-time log data. You must provide an integer between 1 and
-- 100, inclusive.
newUpdateRealtimeLogConfig ::
  UpdateRealtimeLogConfig
newUpdateRealtimeLogConfig :: UpdateRealtimeLogConfig
newUpdateRealtimeLogConfig =
  UpdateRealtimeLogConfig'
    { $sel:arn:UpdateRealtimeLogConfig' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:endPoints:UpdateRealtimeLogConfig' :: Maybe [EndPoint]
endPoints = forall a. Maybe a
Prelude.Nothing,
      $sel:fields:UpdateRealtimeLogConfig' :: Maybe [Text]
fields = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateRealtimeLogConfig' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:samplingRate:UpdateRealtimeLogConfig' :: Maybe Integer
samplingRate = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) for this real-time log configuration.
updateRealtimeLogConfig_arn :: Lens.Lens' UpdateRealtimeLogConfig (Prelude.Maybe Prelude.Text)
updateRealtimeLogConfig_arn :: Lens' UpdateRealtimeLogConfig (Maybe Text)
updateRealtimeLogConfig_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRealtimeLogConfig' {Maybe Text
arn :: Maybe Text
$sel:arn:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe Text
arn} -> Maybe Text
arn) (\s :: UpdateRealtimeLogConfig
s@UpdateRealtimeLogConfig' {} Maybe Text
a -> UpdateRealtimeLogConfig
s {$sel:arn:UpdateRealtimeLogConfig' :: Maybe Text
arn = Maybe Text
a} :: UpdateRealtimeLogConfig)

-- | Contains information about the Amazon Kinesis data stream where you are
-- sending real-time log data.
updateRealtimeLogConfig_endPoints :: Lens.Lens' UpdateRealtimeLogConfig (Prelude.Maybe [EndPoint])
updateRealtimeLogConfig_endPoints :: Lens' UpdateRealtimeLogConfig (Maybe [EndPoint])
updateRealtimeLogConfig_endPoints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRealtimeLogConfig' {Maybe [EndPoint]
endPoints :: Maybe [EndPoint]
$sel:endPoints:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe [EndPoint]
endPoints} -> Maybe [EndPoint]
endPoints) (\s :: UpdateRealtimeLogConfig
s@UpdateRealtimeLogConfig' {} Maybe [EndPoint]
a -> UpdateRealtimeLogConfig
s {$sel:endPoints:UpdateRealtimeLogConfig' :: Maybe [EndPoint]
endPoints = Maybe [EndPoint]
a} :: UpdateRealtimeLogConfig) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A list of fields to include in each real-time log record.
--
-- For more information about fields, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/real-time-logs.html#understand-real-time-log-config-fields Real-time log configuration fields>
-- in the /Amazon CloudFront Developer Guide/.
updateRealtimeLogConfig_fields :: Lens.Lens' UpdateRealtimeLogConfig (Prelude.Maybe [Prelude.Text])
updateRealtimeLogConfig_fields :: Lens' UpdateRealtimeLogConfig (Maybe [Text])
updateRealtimeLogConfig_fields = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRealtimeLogConfig' {Maybe [Text]
fields :: Maybe [Text]
$sel:fields:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe [Text]
fields} -> Maybe [Text]
fields) (\s :: UpdateRealtimeLogConfig
s@UpdateRealtimeLogConfig' {} Maybe [Text]
a -> UpdateRealtimeLogConfig
s {$sel:fields:UpdateRealtimeLogConfig' :: Maybe [Text]
fields = Maybe [Text]
a} :: UpdateRealtimeLogConfig) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The name for this real-time log configuration.
updateRealtimeLogConfig_name :: Lens.Lens' UpdateRealtimeLogConfig (Prelude.Maybe Prelude.Text)
updateRealtimeLogConfig_name :: Lens' UpdateRealtimeLogConfig (Maybe Text)
updateRealtimeLogConfig_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRealtimeLogConfig' {Maybe Text
name :: Maybe Text
$sel:name:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateRealtimeLogConfig
s@UpdateRealtimeLogConfig' {} Maybe Text
a -> UpdateRealtimeLogConfig
s {$sel:name:UpdateRealtimeLogConfig' :: Maybe Text
name = Maybe Text
a} :: UpdateRealtimeLogConfig)

-- | The sampling rate for this real-time log configuration. The sampling
-- rate determines the percentage of viewer requests that are represented
-- in the real-time log data. You must provide an integer between 1 and
-- 100, inclusive.
updateRealtimeLogConfig_samplingRate :: Lens.Lens' UpdateRealtimeLogConfig (Prelude.Maybe Prelude.Integer)
updateRealtimeLogConfig_samplingRate :: Lens' UpdateRealtimeLogConfig (Maybe Integer)
updateRealtimeLogConfig_samplingRate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRealtimeLogConfig' {Maybe Integer
samplingRate :: Maybe Integer
$sel:samplingRate:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe Integer
samplingRate} -> Maybe Integer
samplingRate) (\s :: UpdateRealtimeLogConfig
s@UpdateRealtimeLogConfig' {} Maybe Integer
a -> UpdateRealtimeLogConfig
s {$sel:samplingRate:UpdateRealtimeLogConfig' :: Maybe Integer
samplingRate = Maybe Integer
a} :: UpdateRealtimeLogConfig)

instance Core.AWSRequest UpdateRealtimeLogConfig where
  type
    AWSResponse UpdateRealtimeLogConfig =
      UpdateRealtimeLogConfigResponse
  request :: (Service -> Service)
-> UpdateRealtimeLogConfig -> Request UpdateRealtimeLogConfig
request Service -> Service
overrides =
    forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.putXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateRealtimeLogConfig
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateRealtimeLogConfig)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe RealtimeLogConfig -> Int -> UpdateRealtimeLogConfigResponse
UpdateRealtimeLogConfigResponse'
            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
"RealtimeLogConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable UpdateRealtimeLogConfig where
  hashWithSalt :: Int -> UpdateRealtimeLogConfig -> Int
hashWithSalt Int
_salt UpdateRealtimeLogConfig' {Maybe Integer
Maybe [Text]
Maybe [EndPoint]
Maybe Text
samplingRate :: Maybe Integer
name :: Maybe Text
fields :: Maybe [Text]
endPoints :: Maybe [EndPoint]
arn :: Maybe Text
$sel:samplingRate:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe Integer
$sel:name:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe Text
$sel:fields:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe [Text]
$sel:endPoints:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe [EndPoint]
$sel:arn:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [EndPoint]
endPoints
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
fields
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
samplingRate

instance Prelude.NFData UpdateRealtimeLogConfig where
  rnf :: UpdateRealtimeLogConfig -> ()
rnf UpdateRealtimeLogConfig' {Maybe Integer
Maybe [Text]
Maybe [EndPoint]
Maybe Text
samplingRate :: Maybe Integer
name :: Maybe Text
fields :: Maybe [Text]
endPoints :: Maybe [EndPoint]
arn :: Maybe Text
$sel:samplingRate:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe Integer
$sel:name:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe Text
$sel:fields:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe [Text]
$sel:endPoints:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe [EndPoint]
$sel:arn:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [EndPoint]
endPoints
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
fields
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
samplingRate

instance Data.ToElement UpdateRealtimeLogConfig where
  toElement :: UpdateRealtimeLogConfig -> Element
toElement =
    forall a. ToXML a => Name -> a -> Element
Data.mkElement
      Name
"{http://cloudfront.amazonaws.com/doc/2020-05-31/}UpdateRealtimeLogConfigRequest"

instance Data.ToHeaders UpdateRealtimeLogConfig where
  toHeaders :: UpdateRealtimeLogConfig -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath UpdateRealtimeLogConfig where
  toPath :: UpdateRealtimeLogConfig -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/2020-05-31/realtime-log-config/"

instance Data.ToQuery UpdateRealtimeLogConfig where
  toQuery :: UpdateRealtimeLogConfig -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToXML UpdateRealtimeLogConfig where
  toXML :: UpdateRealtimeLogConfig -> XML
toXML UpdateRealtimeLogConfig' {Maybe Integer
Maybe [Text]
Maybe [EndPoint]
Maybe Text
samplingRate :: Maybe Integer
name :: Maybe Text
fields :: Maybe [Text]
endPoints :: Maybe [EndPoint]
arn :: Maybe Text
$sel:samplingRate:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe Integer
$sel:name:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe Text
$sel:fields:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe [Text]
$sel:endPoints:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe [EndPoint]
$sel:arn:UpdateRealtimeLogConfig' :: UpdateRealtimeLogConfig -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ Name
"ARN" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Text
arn,
        Name
"EndPoints"
          forall a. ToXML a => Name -> a -> XML
Data.@= forall a. ToXML a => a -> XML
Data.toXML
            (forall a. (IsList a, ToXML (Item a)) => Name -> a -> XML
Data.toXMLList Name
"member" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [EndPoint]
endPoints),
        Name
"Fields"
          forall a. ToXML a => Name -> a -> XML
Data.@= forall a. ToXML a => a -> XML
Data.toXML
            (forall a. (IsList a, ToXML (Item a)) => Name -> a -> XML
Data.toXMLList Name
"Field" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
fields),
        Name
"Name" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Text
name,
        Name
"SamplingRate" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Integer
samplingRate
      ]

-- | /See:/ 'newUpdateRealtimeLogConfigResponse' smart constructor.
data UpdateRealtimeLogConfigResponse = UpdateRealtimeLogConfigResponse'
  { -- | A real-time log configuration.
    UpdateRealtimeLogConfigResponse -> Maybe RealtimeLogConfig
realtimeLogConfig :: Prelude.Maybe RealtimeLogConfig,
    -- | The response's http status code.
    UpdateRealtimeLogConfigResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateRealtimeLogConfigResponse
-> UpdateRealtimeLogConfigResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRealtimeLogConfigResponse
-> UpdateRealtimeLogConfigResponse -> Bool
$c/= :: UpdateRealtimeLogConfigResponse
-> UpdateRealtimeLogConfigResponse -> Bool
== :: UpdateRealtimeLogConfigResponse
-> UpdateRealtimeLogConfigResponse -> Bool
$c== :: UpdateRealtimeLogConfigResponse
-> UpdateRealtimeLogConfigResponse -> Bool
Prelude.Eq, ReadPrec [UpdateRealtimeLogConfigResponse]
ReadPrec UpdateRealtimeLogConfigResponse
Int -> ReadS UpdateRealtimeLogConfigResponse
ReadS [UpdateRealtimeLogConfigResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRealtimeLogConfigResponse]
$creadListPrec :: ReadPrec [UpdateRealtimeLogConfigResponse]
readPrec :: ReadPrec UpdateRealtimeLogConfigResponse
$creadPrec :: ReadPrec UpdateRealtimeLogConfigResponse
readList :: ReadS [UpdateRealtimeLogConfigResponse]
$creadList :: ReadS [UpdateRealtimeLogConfigResponse]
readsPrec :: Int -> ReadS UpdateRealtimeLogConfigResponse
$creadsPrec :: Int -> ReadS UpdateRealtimeLogConfigResponse
Prelude.Read, Int -> UpdateRealtimeLogConfigResponse -> ShowS
[UpdateRealtimeLogConfigResponse] -> ShowS
UpdateRealtimeLogConfigResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRealtimeLogConfigResponse] -> ShowS
$cshowList :: [UpdateRealtimeLogConfigResponse] -> ShowS
show :: UpdateRealtimeLogConfigResponse -> String
$cshow :: UpdateRealtimeLogConfigResponse -> String
showsPrec :: Int -> UpdateRealtimeLogConfigResponse -> ShowS
$cshowsPrec :: Int -> UpdateRealtimeLogConfigResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateRealtimeLogConfigResponse x
-> UpdateRealtimeLogConfigResponse
forall x.
UpdateRealtimeLogConfigResponse
-> Rep UpdateRealtimeLogConfigResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateRealtimeLogConfigResponse x
-> UpdateRealtimeLogConfigResponse
$cfrom :: forall x.
UpdateRealtimeLogConfigResponse
-> Rep UpdateRealtimeLogConfigResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRealtimeLogConfigResponse' 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:
--
-- 'realtimeLogConfig', 'updateRealtimeLogConfigResponse_realtimeLogConfig' - A real-time log configuration.
--
-- 'httpStatus', 'updateRealtimeLogConfigResponse_httpStatus' - The response's http status code.
newUpdateRealtimeLogConfigResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateRealtimeLogConfigResponse
newUpdateRealtimeLogConfigResponse :: Int -> UpdateRealtimeLogConfigResponse
newUpdateRealtimeLogConfigResponse Int
pHttpStatus_ =
  UpdateRealtimeLogConfigResponse'
    { $sel:realtimeLogConfig:UpdateRealtimeLogConfigResponse' :: Maybe RealtimeLogConfig
realtimeLogConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateRealtimeLogConfigResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A real-time log configuration.
updateRealtimeLogConfigResponse_realtimeLogConfig :: Lens.Lens' UpdateRealtimeLogConfigResponse (Prelude.Maybe RealtimeLogConfig)
updateRealtimeLogConfigResponse_realtimeLogConfig :: Lens' UpdateRealtimeLogConfigResponse (Maybe RealtimeLogConfig)
updateRealtimeLogConfigResponse_realtimeLogConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRealtimeLogConfigResponse' {Maybe RealtimeLogConfig
realtimeLogConfig :: Maybe RealtimeLogConfig
$sel:realtimeLogConfig:UpdateRealtimeLogConfigResponse' :: UpdateRealtimeLogConfigResponse -> Maybe RealtimeLogConfig
realtimeLogConfig} -> Maybe RealtimeLogConfig
realtimeLogConfig) (\s :: UpdateRealtimeLogConfigResponse
s@UpdateRealtimeLogConfigResponse' {} Maybe RealtimeLogConfig
a -> UpdateRealtimeLogConfigResponse
s {$sel:realtimeLogConfig:UpdateRealtimeLogConfigResponse' :: Maybe RealtimeLogConfig
realtimeLogConfig = Maybe RealtimeLogConfig
a} :: UpdateRealtimeLogConfigResponse)

-- | The response's http status code.
updateRealtimeLogConfigResponse_httpStatus :: Lens.Lens' UpdateRealtimeLogConfigResponse Prelude.Int
updateRealtimeLogConfigResponse_httpStatus :: Lens' UpdateRealtimeLogConfigResponse Int
updateRealtimeLogConfigResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRealtimeLogConfigResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateRealtimeLogConfigResponse' :: UpdateRealtimeLogConfigResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateRealtimeLogConfigResponse
s@UpdateRealtimeLogConfigResponse' {} Int
a -> UpdateRealtimeLogConfigResponse
s {$sel:httpStatus:UpdateRealtimeLogConfigResponse' :: Int
httpStatus = Int
a} :: UpdateRealtimeLogConfigResponse)

instance
  Prelude.NFData
    UpdateRealtimeLogConfigResponse
  where
  rnf :: UpdateRealtimeLogConfigResponse -> ()
rnf UpdateRealtimeLogConfigResponse' {Int
Maybe RealtimeLogConfig
httpStatus :: Int
realtimeLogConfig :: Maybe RealtimeLogConfig
$sel:httpStatus:UpdateRealtimeLogConfigResponse' :: UpdateRealtimeLogConfigResponse -> Int
$sel:realtimeLogConfig:UpdateRealtimeLogConfigResponse' :: UpdateRealtimeLogConfigResponse -> Maybe RealtimeLogConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe RealtimeLogConfig
realtimeLogConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus