{-# 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.NetworkFirewall.DescribeLoggingConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the logging configuration for the specified firewall.
module Amazonka.NetworkFirewall.DescribeLoggingConfiguration
  ( -- * Creating a Request
    DescribeLoggingConfiguration (..),
    newDescribeLoggingConfiguration,

    -- * Request Lenses
    describeLoggingConfiguration_firewallArn,
    describeLoggingConfiguration_firewallName,

    -- * Destructuring the Response
    DescribeLoggingConfigurationResponse (..),
    newDescribeLoggingConfigurationResponse,

    -- * Response Lenses
    describeLoggingConfigurationResponse_firewallArn,
    describeLoggingConfigurationResponse_loggingConfiguration,
    describeLoggingConfigurationResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.NetworkFirewall.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeLoggingConfiguration' smart constructor.
data DescribeLoggingConfiguration = DescribeLoggingConfiguration'
  { -- | The Amazon Resource Name (ARN) of the firewall.
    --
    -- You must specify the ARN or the name, and you can specify both.
    DescribeLoggingConfiguration -> Maybe Text
firewallArn :: Prelude.Maybe Prelude.Text,
    -- | The descriptive name of the firewall. You can\'t change the name of a
    -- firewall after you create it.
    --
    -- You must specify the ARN or the name, and you can specify both.
    DescribeLoggingConfiguration -> Maybe Text
firewallName :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeLoggingConfiguration
-> DescribeLoggingConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLoggingConfiguration
-> DescribeLoggingConfiguration -> Bool
$c/= :: DescribeLoggingConfiguration
-> DescribeLoggingConfiguration -> Bool
== :: DescribeLoggingConfiguration
-> DescribeLoggingConfiguration -> Bool
$c== :: DescribeLoggingConfiguration
-> DescribeLoggingConfiguration -> Bool
Prelude.Eq, ReadPrec [DescribeLoggingConfiguration]
ReadPrec DescribeLoggingConfiguration
Int -> ReadS DescribeLoggingConfiguration
ReadS [DescribeLoggingConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLoggingConfiguration]
$creadListPrec :: ReadPrec [DescribeLoggingConfiguration]
readPrec :: ReadPrec DescribeLoggingConfiguration
$creadPrec :: ReadPrec DescribeLoggingConfiguration
readList :: ReadS [DescribeLoggingConfiguration]
$creadList :: ReadS [DescribeLoggingConfiguration]
readsPrec :: Int -> ReadS DescribeLoggingConfiguration
$creadsPrec :: Int -> ReadS DescribeLoggingConfiguration
Prelude.Read, Int -> DescribeLoggingConfiguration -> ShowS
[DescribeLoggingConfiguration] -> ShowS
DescribeLoggingConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLoggingConfiguration] -> ShowS
$cshowList :: [DescribeLoggingConfiguration] -> ShowS
show :: DescribeLoggingConfiguration -> String
$cshow :: DescribeLoggingConfiguration -> String
showsPrec :: Int -> DescribeLoggingConfiguration -> ShowS
$cshowsPrec :: Int -> DescribeLoggingConfiguration -> ShowS
Prelude.Show, forall x.
Rep DescribeLoggingConfiguration x -> DescribeLoggingConfiguration
forall x.
DescribeLoggingConfiguration -> Rep DescribeLoggingConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLoggingConfiguration x -> DescribeLoggingConfiguration
$cfrom :: forall x.
DescribeLoggingConfiguration -> Rep DescribeLoggingConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLoggingConfiguration' 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:
--
-- 'firewallArn', 'describeLoggingConfiguration_firewallArn' - The Amazon Resource Name (ARN) of the firewall.
--
-- You must specify the ARN or the name, and you can specify both.
--
-- 'firewallName', 'describeLoggingConfiguration_firewallName' - The descriptive name of the firewall. You can\'t change the name of a
-- firewall after you create it.
--
-- You must specify the ARN or the name, and you can specify both.
newDescribeLoggingConfiguration ::
  DescribeLoggingConfiguration
newDescribeLoggingConfiguration :: DescribeLoggingConfiguration
newDescribeLoggingConfiguration =
  DescribeLoggingConfiguration'
    { $sel:firewallArn:DescribeLoggingConfiguration' :: Maybe Text
firewallArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:firewallName:DescribeLoggingConfiguration' :: Maybe Text
firewallName = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the firewall.
--
-- You must specify the ARN or the name, and you can specify both.
describeLoggingConfiguration_firewallArn :: Lens.Lens' DescribeLoggingConfiguration (Prelude.Maybe Prelude.Text)
describeLoggingConfiguration_firewallArn :: Lens' DescribeLoggingConfiguration (Maybe Text)
describeLoggingConfiguration_firewallArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLoggingConfiguration' {Maybe Text
firewallArn :: Maybe Text
$sel:firewallArn:DescribeLoggingConfiguration' :: DescribeLoggingConfiguration -> Maybe Text
firewallArn} -> Maybe Text
firewallArn) (\s :: DescribeLoggingConfiguration
s@DescribeLoggingConfiguration' {} Maybe Text
a -> DescribeLoggingConfiguration
s {$sel:firewallArn:DescribeLoggingConfiguration' :: Maybe Text
firewallArn = Maybe Text
a} :: DescribeLoggingConfiguration)

-- | The descriptive name of the firewall. You can\'t change the name of a
-- firewall after you create it.
--
-- You must specify the ARN or the name, and you can specify both.
describeLoggingConfiguration_firewallName :: Lens.Lens' DescribeLoggingConfiguration (Prelude.Maybe Prelude.Text)
describeLoggingConfiguration_firewallName :: Lens' DescribeLoggingConfiguration (Maybe Text)
describeLoggingConfiguration_firewallName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLoggingConfiguration' {Maybe Text
firewallName :: Maybe Text
$sel:firewallName:DescribeLoggingConfiguration' :: DescribeLoggingConfiguration -> Maybe Text
firewallName} -> Maybe Text
firewallName) (\s :: DescribeLoggingConfiguration
s@DescribeLoggingConfiguration' {} Maybe Text
a -> DescribeLoggingConfiguration
s {$sel:firewallName:DescribeLoggingConfiguration' :: Maybe Text
firewallName = Maybe Text
a} :: DescribeLoggingConfiguration)

instance Core.AWSRequest DescribeLoggingConfiguration where
  type
    AWSResponse DescribeLoggingConfiguration =
      DescribeLoggingConfigurationResponse
  request :: (Service -> Service)
-> DescribeLoggingConfiguration
-> Request DescribeLoggingConfiguration
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeLoggingConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeLoggingConfiguration)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe LoggingConfiguration
-> Int
-> DescribeLoggingConfigurationResponse
DescribeLoggingConfigurationResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"FirewallArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LoggingConfiguration")
            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
    DescribeLoggingConfiguration
  where
  hashWithSalt :: Int -> DescribeLoggingConfiguration -> Int
hashWithSalt Int
_salt DescribeLoggingConfiguration' {Maybe Text
firewallName :: Maybe Text
firewallArn :: Maybe Text
$sel:firewallName:DescribeLoggingConfiguration' :: DescribeLoggingConfiguration -> Maybe Text
$sel:firewallArn:DescribeLoggingConfiguration' :: DescribeLoggingConfiguration -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
firewallArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
firewallName

instance Prelude.NFData DescribeLoggingConfiguration where
  rnf :: DescribeLoggingConfiguration -> ()
rnf DescribeLoggingConfiguration' {Maybe Text
firewallName :: Maybe Text
firewallArn :: Maybe Text
$sel:firewallName:DescribeLoggingConfiguration' :: DescribeLoggingConfiguration -> Maybe Text
$sel:firewallArn:DescribeLoggingConfiguration' :: DescribeLoggingConfiguration -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
firewallArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
firewallName

instance Data.ToHeaders DescribeLoggingConfiguration where
  toHeaders :: DescribeLoggingConfiguration -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"NetworkFirewall_20201112.DescribeLoggingConfiguration" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeLoggingConfiguration where
  toJSON :: DescribeLoggingConfiguration -> Value
toJSON DescribeLoggingConfiguration' {Maybe Text
firewallName :: Maybe Text
firewallArn :: Maybe Text
$sel:firewallName:DescribeLoggingConfiguration' :: DescribeLoggingConfiguration -> Maybe Text
$sel:firewallArn:DescribeLoggingConfiguration' :: DescribeLoggingConfiguration -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"FirewallArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
firewallArn,
            (Key
"FirewallName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
firewallName
          ]
      )

instance Data.ToPath DescribeLoggingConfiguration where
  toPath :: DescribeLoggingConfiguration -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDescribeLoggingConfigurationResponse' smart constructor.
data DescribeLoggingConfigurationResponse = DescribeLoggingConfigurationResponse'
  { -- | The Amazon Resource Name (ARN) of the firewall.
    DescribeLoggingConfigurationResponse -> Maybe Text
firewallArn :: Prelude.Maybe Prelude.Text,
    DescribeLoggingConfigurationResponse -> Maybe LoggingConfiguration
loggingConfiguration :: Prelude.Maybe LoggingConfiguration,
    -- | The response's http status code.
    DescribeLoggingConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeLoggingConfigurationResponse
-> DescribeLoggingConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLoggingConfigurationResponse
-> DescribeLoggingConfigurationResponse -> Bool
$c/= :: DescribeLoggingConfigurationResponse
-> DescribeLoggingConfigurationResponse -> Bool
== :: DescribeLoggingConfigurationResponse
-> DescribeLoggingConfigurationResponse -> Bool
$c== :: DescribeLoggingConfigurationResponse
-> DescribeLoggingConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [DescribeLoggingConfigurationResponse]
ReadPrec DescribeLoggingConfigurationResponse
Int -> ReadS DescribeLoggingConfigurationResponse
ReadS [DescribeLoggingConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLoggingConfigurationResponse]
$creadListPrec :: ReadPrec [DescribeLoggingConfigurationResponse]
readPrec :: ReadPrec DescribeLoggingConfigurationResponse
$creadPrec :: ReadPrec DescribeLoggingConfigurationResponse
readList :: ReadS [DescribeLoggingConfigurationResponse]
$creadList :: ReadS [DescribeLoggingConfigurationResponse]
readsPrec :: Int -> ReadS DescribeLoggingConfigurationResponse
$creadsPrec :: Int -> ReadS DescribeLoggingConfigurationResponse
Prelude.Read, Int -> DescribeLoggingConfigurationResponse -> ShowS
[DescribeLoggingConfigurationResponse] -> ShowS
DescribeLoggingConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLoggingConfigurationResponse] -> ShowS
$cshowList :: [DescribeLoggingConfigurationResponse] -> ShowS
show :: DescribeLoggingConfigurationResponse -> String
$cshow :: DescribeLoggingConfigurationResponse -> String
showsPrec :: Int -> DescribeLoggingConfigurationResponse -> ShowS
$cshowsPrec :: Int -> DescribeLoggingConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeLoggingConfigurationResponse x
-> DescribeLoggingConfigurationResponse
forall x.
DescribeLoggingConfigurationResponse
-> Rep DescribeLoggingConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLoggingConfigurationResponse x
-> DescribeLoggingConfigurationResponse
$cfrom :: forall x.
DescribeLoggingConfigurationResponse
-> Rep DescribeLoggingConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLoggingConfigurationResponse' 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:
--
-- 'firewallArn', 'describeLoggingConfigurationResponse_firewallArn' - The Amazon Resource Name (ARN) of the firewall.
--
-- 'loggingConfiguration', 'describeLoggingConfigurationResponse_loggingConfiguration' - Undocumented member.
--
-- 'httpStatus', 'describeLoggingConfigurationResponse_httpStatus' - The response's http status code.
newDescribeLoggingConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeLoggingConfigurationResponse
newDescribeLoggingConfigurationResponse :: Int -> DescribeLoggingConfigurationResponse
newDescribeLoggingConfigurationResponse Int
pHttpStatus_ =
  DescribeLoggingConfigurationResponse'
    { $sel:firewallArn:DescribeLoggingConfigurationResponse' :: Maybe Text
firewallArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:loggingConfiguration:DescribeLoggingConfigurationResponse' :: Maybe LoggingConfiguration
loggingConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeLoggingConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the firewall.
describeLoggingConfigurationResponse_firewallArn :: Lens.Lens' DescribeLoggingConfigurationResponse (Prelude.Maybe Prelude.Text)
describeLoggingConfigurationResponse_firewallArn :: Lens' DescribeLoggingConfigurationResponse (Maybe Text)
describeLoggingConfigurationResponse_firewallArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLoggingConfigurationResponse' {Maybe Text
firewallArn :: Maybe Text
$sel:firewallArn:DescribeLoggingConfigurationResponse' :: DescribeLoggingConfigurationResponse -> Maybe Text
firewallArn} -> Maybe Text
firewallArn) (\s :: DescribeLoggingConfigurationResponse
s@DescribeLoggingConfigurationResponse' {} Maybe Text
a -> DescribeLoggingConfigurationResponse
s {$sel:firewallArn:DescribeLoggingConfigurationResponse' :: Maybe Text
firewallArn = Maybe Text
a} :: DescribeLoggingConfigurationResponse)

-- | Undocumented member.
describeLoggingConfigurationResponse_loggingConfiguration :: Lens.Lens' DescribeLoggingConfigurationResponse (Prelude.Maybe LoggingConfiguration)
describeLoggingConfigurationResponse_loggingConfiguration :: Lens'
  DescribeLoggingConfigurationResponse (Maybe LoggingConfiguration)
describeLoggingConfigurationResponse_loggingConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLoggingConfigurationResponse' {Maybe LoggingConfiguration
loggingConfiguration :: Maybe LoggingConfiguration
$sel:loggingConfiguration:DescribeLoggingConfigurationResponse' :: DescribeLoggingConfigurationResponse -> Maybe LoggingConfiguration
loggingConfiguration} -> Maybe LoggingConfiguration
loggingConfiguration) (\s :: DescribeLoggingConfigurationResponse
s@DescribeLoggingConfigurationResponse' {} Maybe LoggingConfiguration
a -> DescribeLoggingConfigurationResponse
s {$sel:loggingConfiguration:DescribeLoggingConfigurationResponse' :: Maybe LoggingConfiguration
loggingConfiguration = Maybe LoggingConfiguration
a} :: DescribeLoggingConfigurationResponse)

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

instance
  Prelude.NFData
    DescribeLoggingConfigurationResponse
  where
  rnf :: DescribeLoggingConfigurationResponse -> ()
rnf DescribeLoggingConfigurationResponse' {Int
Maybe Text
Maybe LoggingConfiguration
httpStatus :: Int
loggingConfiguration :: Maybe LoggingConfiguration
firewallArn :: Maybe Text
$sel:httpStatus:DescribeLoggingConfigurationResponse' :: DescribeLoggingConfigurationResponse -> Int
$sel:loggingConfiguration:DescribeLoggingConfigurationResponse' :: DescribeLoggingConfigurationResponse -> Maybe LoggingConfiguration
$sel:firewallArn:DescribeLoggingConfigurationResponse' :: DescribeLoggingConfigurationResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
firewallArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LoggingConfiguration
loggingConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus