{-# 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.GetRealtimeLogConfig
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets a real-time log configuration.
--
-- To get a real-time log configuration, you can provide the
-- configuration\'s name or its Amazon Resource Name (ARN). You must
-- provide at least one. If you provide both, CloudFront uses the name to
-- identify the real-time log configuration to get.
module Amazonka.CloudFront.GetRealtimeLogConfig
  ( -- * Creating a Request
    GetRealtimeLogConfig (..),
    newGetRealtimeLogConfig,

    -- * Request Lenses
    getRealtimeLogConfig_arn,
    getRealtimeLogConfig_name,

    -- * Destructuring the Response
    GetRealtimeLogConfigResponse (..),
    newGetRealtimeLogConfigResponse,

    -- * Response Lenses
    getRealtimeLogConfigResponse_realtimeLogConfig,
    getRealtimeLogConfigResponse_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:/ 'newGetRealtimeLogConfig' smart constructor.
data GetRealtimeLogConfig = GetRealtimeLogConfig'
  { -- | The Amazon Resource Name (ARN) of the real-time log configuration to
    -- get.
    GetRealtimeLogConfig -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The name of the real-time log configuration to get.
    GetRealtimeLogConfig -> Maybe Text
name :: Prelude.Maybe Prelude.Text
  }
  deriving (GetRealtimeLogConfig -> GetRealtimeLogConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRealtimeLogConfig -> GetRealtimeLogConfig -> Bool
$c/= :: GetRealtimeLogConfig -> GetRealtimeLogConfig -> Bool
== :: GetRealtimeLogConfig -> GetRealtimeLogConfig -> Bool
$c== :: GetRealtimeLogConfig -> GetRealtimeLogConfig -> Bool
Prelude.Eq, ReadPrec [GetRealtimeLogConfig]
ReadPrec GetRealtimeLogConfig
Int -> ReadS GetRealtimeLogConfig
ReadS [GetRealtimeLogConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRealtimeLogConfig]
$creadListPrec :: ReadPrec [GetRealtimeLogConfig]
readPrec :: ReadPrec GetRealtimeLogConfig
$creadPrec :: ReadPrec GetRealtimeLogConfig
readList :: ReadS [GetRealtimeLogConfig]
$creadList :: ReadS [GetRealtimeLogConfig]
readsPrec :: Int -> ReadS GetRealtimeLogConfig
$creadsPrec :: Int -> ReadS GetRealtimeLogConfig
Prelude.Read, Int -> GetRealtimeLogConfig -> ShowS
[GetRealtimeLogConfig] -> ShowS
GetRealtimeLogConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRealtimeLogConfig] -> ShowS
$cshowList :: [GetRealtimeLogConfig] -> ShowS
show :: GetRealtimeLogConfig -> String
$cshow :: GetRealtimeLogConfig -> String
showsPrec :: Int -> GetRealtimeLogConfig -> ShowS
$cshowsPrec :: Int -> GetRealtimeLogConfig -> ShowS
Prelude.Show, forall x. Rep GetRealtimeLogConfig x -> GetRealtimeLogConfig
forall x. GetRealtimeLogConfig -> Rep GetRealtimeLogConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRealtimeLogConfig x -> GetRealtimeLogConfig
$cfrom :: forall x. GetRealtimeLogConfig -> Rep GetRealtimeLogConfig x
Prelude.Generic)

-- |
-- Create a value of 'GetRealtimeLogConfig' 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', 'getRealtimeLogConfig_arn' - The Amazon Resource Name (ARN) of the real-time log configuration to
-- get.
--
-- 'name', 'getRealtimeLogConfig_name' - The name of the real-time log configuration to get.
newGetRealtimeLogConfig ::
  GetRealtimeLogConfig
newGetRealtimeLogConfig :: GetRealtimeLogConfig
newGetRealtimeLogConfig =
  GetRealtimeLogConfig'
    { $sel:arn:GetRealtimeLogConfig' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetRealtimeLogConfig' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the real-time log configuration to
-- get.
getRealtimeLogConfig_arn :: Lens.Lens' GetRealtimeLogConfig (Prelude.Maybe Prelude.Text)
getRealtimeLogConfig_arn :: Lens' GetRealtimeLogConfig (Maybe Text)
getRealtimeLogConfig_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRealtimeLogConfig' {Maybe Text
arn :: Maybe Text
$sel:arn:GetRealtimeLogConfig' :: GetRealtimeLogConfig -> Maybe Text
arn} -> Maybe Text
arn) (\s :: GetRealtimeLogConfig
s@GetRealtimeLogConfig' {} Maybe Text
a -> GetRealtimeLogConfig
s {$sel:arn:GetRealtimeLogConfig' :: Maybe Text
arn = Maybe Text
a} :: GetRealtimeLogConfig)

-- | The name of the real-time log configuration to get.
getRealtimeLogConfig_name :: Lens.Lens' GetRealtimeLogConfig (Prelude.Maybe Prelude.Text)
getRealtimeLogConfig_name :: Lens' GetRealtimeLogConfig (Maybe Text)
getRealtimeLogConfig_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRealtimeLogConfig' {Maybe Text
name :: Maybe Text
$sel:name:GetRealtimeLogConfig' :: GetRealtimeLogConfig -> Maybe Text
name} -> Maybe Text
name) (\s :: GetRealtimeLogConfig
s@GetRealtimeLogConfig' {} Maybe Text
a -> GetRealtimeLogConfig
s {$sel:name:GetRealtimeLogConfig' :: Maybe Text
name = Maybe Text
a} :: GetRealtimeLogConfig)

instance Core.AWSRequest GetRealtimeLogConfig where
  type
    AWSResponse GetRealtimeLogConfig =
      GetRealtimeLogConfigResponse
  request :: (Service -> Service)
-> GetRealtimeLogConfig -> Request GetRealtimeLogConfig
request Service -> Service
overrides =
    forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.postXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetRealtimeLogConfig
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetRealtimeLogConfig)))
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 -> GetRealtimeLogConfigResponse
GetRealtimeLogConfigResponse'
            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 GetRealtimeLogConfig where
  hashWithSalt :: Int -> GetRealtimeLogConfig -> Int
hashWithSalt Int
_salt GetRealtimeLogConfig' {Maybe Text
name :: Maybe Text
arn :: Maybe Text
$sel:name:GetRealtimeLogConfig' :: GetRealtimeLogConfig -> Maybe Text
$sel:arn:GetRealtimeLogConfig' :: GetRealtimeLogConfig -> 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 Text
name

instance Prelude.NFData GetRealtimeLogConfig where
  rnf :: GetRealtimeLogConfig -> ()
rnf GetRealtimeLogConfig' {Maybe Text
name :: Maybe Text
arn :: Maybe Text
$sel:name:GetRealtimeLogConfig' :: GetRealtimeLogConfig -> Maybe Text
$sel:arn:GetRealtimeLogConfig' :: GetRealtimeLogConfig -> 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 Text
name

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

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

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

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

instance Data.ToXML GetRealtimeLogConfig where
  toXML :: GetRealtimeLogConfig -> XML
toXML GetRealtimeLogConfig' {Maybe Text
name :: Maybe Text
arn :: Maybe Text
$sel:name:GetRealtimeLogConfig' :: GetRealtimeLogConfig -> Maybe Text
$sel:arn:GetRealtimeLogConfig' :: GetRealtimeLogConfig -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [Name
"ARN" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Text
arn, Name
"Name" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Text
name]

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

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

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

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

instance Prelude.NFData GetRealtimeLogConfigResponse where
  rnf :: GetRealtimeLogConfigResponse -> ()
rnf GetRealtimeLogConfigResponse' {Int
Maybe RealtimeLogConfig
httpStatus :: Int
realtimeLogConfig :: Maybe RealtimeLogConfig
$sel:httpStatus:GetRealtimeLogConfigResponse' :: GetRealtimeLogConfigResponse -> Int
$sel:realtimeLogConfig:GetRealtimeLogConfigResponse' :: GetRealtimeLogConfigResponse -> 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