{-# 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.AMP.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)
--
-- Describes logging configuration.
module Amazonka.AMP.DescribeLoggingConfiguration
  ( -- * Creating a Request
    DescribeLoggingConfiguration (..),
    newDescribeLoggingConfiguration,

    -- * Request Lenses
    describeLoggingConfiguration_workspaceId,

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

    -- * Response Lenses
    describeLoggingConfigurationResponse_httpStatus,
    describeLoggingConfigurationResponse_loggingConfiguration,
  )
where

import Amazonka.AMP.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

-- | Represents the input of a DescribeLoggingConfiguration operation.
--
-- /See:/ 'newDescribeLoggingConfiguration' smart constructor.
data DescribeLoggingConfiguration = DescribeLoggingConfiguration'
  { -- | The ID of the workspace to vend logs to.
    DescribeLoggingConfiguration -> Text
workspaceId :: 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:
--
-- 'workspaceId', 'describeLoggingConfiguration_workspaceId' - The ID of the workspace to vend logs to.
newDescribeLoggingConfiguration ::
  -- | 'workspaceId'
  Prelude.Text ->
  DescribeLoggingConfiguration
newDescribeLoggingConfiguration :: Text -> DescribeLoggingConfiguration
newDescribeLoggingConfiguration Text
pWorkspaceId_ =
  DescribeLoggingConfiguration'
    { $sel:workspaceId:DescribeLoggingConfiguration' :: Text
workspaceId =
        Text
pWorkspaceId_
    }

-- | The ID of the workspace to vend logs to.
describeLoggingConfiguration_workspaceId :: Lens.Lens' DescribeLoggingConfiguration Prelude.Text
describeLoggingConfiguration_workspaceId :: Lens' DescribeLoggingConfiguration Text
describeLoggingConfiguration_workspaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLoggingConfiguration' {Text
workspaceId :: Text
$sel:workspaceId:DescribeLoggingConfiguration' :: DescribeLoggingConfiguration -> Text
workspaceId} -> Text
workspaceId) (\s :: DescribeLoggingConfiguration
s@DescribeLoggingConfiguration' {} Text
a -> DescribeLoggingConfiguration
s {$sel:workspaceId:DescribeLoggingConfiguration' :: Text
workspaceId = 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 => Service -> a -> Request a
Request.get (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 ->
          Int
-> LoggingConfigurationMetadata
-> DescribeLoggingConfigurationResponse
DescribeLoggingConfigurationResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"loggingConfiguration")
      )

instance
  Prelude.Hashable
    DescribeLoggingConfiguration
  where
  hashWithSalt :: Int -> DescribeLoggingConfiguration -> Int
hashWithSalt Int
_salt DescribeLoggingConfiguration' {Text
workspaceId :: Text
$sel:workspaceId:DescribeLoggingConfiguration' :: DescribeLoggingConfiguration -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workspaceId

instance Prelude.NFData DescribeLoggingConfiguration where
  rnf :: DescribeLoggingConfiguration -> ()
rnf DescribeLoggingConfiguration' {Text
workspaceId :: Text
$sel:workspaceId:DescribeLoggingConfiguration' :: DescribeLoggingConfiguration -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
workspaceId

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
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath DescribeLoggingConfiguration where
  toPath :: DescribeLoggingConfiguration -> ByteString
toPath DescribeLoggingConfiguration' {Text
workspaceId :: Text
$sel:workspaceId:DescribeLoggingConfiguration' :: DescribeLoggingConfiguration -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/workspaces/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
workspaceId, ByteString
"/logging"]

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

-- | Represents the output of a DescribeLoggingConfiguration operation.
--
-- /See:/ 'newDescribeLoggingConfigurationResponse' smart constructor.
data DescribeLoggingConfigurationResponse = DescribeLoggingConfigurationResponse'
  { -- | The response's http status code.
    DescribeLoggingConfigurationResponse -> Int
httpStatus :: Prelude.Int,
    -- | Metadata object containing information about the logging configuration
    -- of a workspace.
    DescribeLoggingConfigurationResponse
-> LoggingConfigurationMetadata
loggingConfiguration :: LoggingConfigurationMetadata
  }
  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:
--
-- 'httpStatus', 'describeLoggingConfigurationResponse_httpStatus' - The response's http status code.
--
-- 'loggingConfiguration', 'describeLoggingConfigurationResponse_loggingConfiguration' - Metadata object containing information about the logging configuration
-- of a workspace.
newDescribeLoggingConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'loggingConfiguration'
  LoggingConfigurationMetadata ->
  DescribeLoggingConfigurationResponse
newDescribeLoggingConfigurationResponse :: Int
-> LoggingConfigurationMetadata
-> DescribeLoggingConfigurationResponse
newDescribeLoggingConfigurationResponse
  Int
pHttpStatus_
  LoggingConfigurationMetadata
pLoggingConfiguration_ =
    DescribeLoggingConfigurationResponse'
      { $sel:httpStatus:DescribeLoggingConfigurationResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:loggingConfiguration:DescribeLoggingConfigurationResponse' :: LoggingConfigurationMetadata
loggingConfiguration =
          LoggingConfigurationMetadata
pLoggingConfiguration_
      }

-- | 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)

-- | Metadata object containing information about the logging configuration
-- of a workspace.
describeLoggingConfigurationResponse_loggingConfiguration :: Lens.Lens' DescribeLoggingConfigurationResponse LoggingConfigurationMetadata
describeLoggingConfigurationResponse_loggingConfiguration :: Lens'
  DescribeLoggingConfigurationResponse LoggingConfigurationMetadata
describeLoggingConfigurationResponse_loggingConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLoggingConfigurationResponse' {LoggingConfigurationMetadata
loggingConfiguration :: LoggingConfigurationMetadata
$sel:loggingConfiguration:DescribeLoggingConfigurationResponse' :: DescribeLoggingConfigurationResponse
-> LoggingConfigurationMetadata
loggingConfiguration} -> LoggingConfigurationMetadata
loggingConfiguration) (\s :: DescribeLoggingConfigurationResponse
s@DescribeLoggingConfigurationResponse' {} LoggingConfigurationMetadata
a -> DescribeLoggingConfigurationResponse
s {$sel:loggingConfiguration:DescribeLoggingConfigurationResponse' :: LoggingConfigurationMetadata
loggingConfiguration = LoggingConfigurationMetadata
a} :: DescribeLoggingConfigurationResponse)

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