{-# 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.XRay.GetEncryptionConfig
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the current encryption configuration for X-Ray data.
module Amazonka.XRay.GetEncryptionConfig
  ( -- * Creating a Request
    GetEncryptionConfig (..),
    newGetEncryptionConfig,

    -- * Destructuring the Response
    GetEncryptionConfigResponse (..),
    newGetEncryptionConfigResponse,

    -- * Response Lenses
    getEncryptionConfigResponse_encryptionConfig,
    getEncryptionConfigResponse_httpStatus,
  )
where

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
import Amazonka.XRay.Types

-- | /See:/ 'newGetEncryptionConfig' smart constructor.
data GetEncryptionConfig = GetEncryptionConfig'
  {
  }
  deriving (GetEncryptionConfig -> GetEncryptionConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEncryptionConfig -> GetEncryptionConfig -> Bool
$c/= :: GetEncryptionConfig -> GetEncryptionConfig -> Bool
== :: GetEncryptionConfig -> GetEncryptionConfig -> Bool
$c== :: GetEncryptionConfig -> GetEncryptionConfig -> Bool
Prelude.Eq, ReadPrec [GetEncryptionConfig]
ReadPrec GetEncryptionConfig
Int -> ReadS GetEncryptionConfig
ReadS [GetEncryptionConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetEncryptionConfig]
$creadListPrec :: ReadPrec [GetEncryptionConfig]
readPrec :: ReadPrec GetEncryptionConfig
$creadPrec :: ReadPrec GetEncryptionConfig
readList :: ReadS [GetEncryptionConfig]
$creadList :: ReadS [GetEncryptionConfig]
readsPrec :: Int -> ReadS GetEncryptionConfig
$creadsPrec :: Int -> ReadS GetEncryptionConfig
Prelude.Read, Int -> GetEncryptionConfig -> ShowS
[GetEncryptionConfig] -> ShowS
GetEncryptionConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEncryptionConfig] -> ShowS
$cshowList :: [GetEncryptionConfig] -> ShowS
show :: GetEncryptionConfig -> String
$cshow :: GetEncryptionConfig -> String
showsPrec :: Int -> GetEncryptionConfig -> ShowS
$cshowsPrec :: Int -> GetEncryptionConfig -> ShowS
Prelude.Show, forall x. Rep GetEncryptionConfig x -> GetEncryptionConfig
forall x. GetEncryptionConfig -> Rep GetEncryptionConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetEncryptionConfig x -> GetEncryptionConfig
$cfrom :: forall x. GetEncryptionConfig -> Rep GetEncryptionConfig x
Prelude.Generic)

-- |
-- Create a value of 'GetEncryptionConfig' 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.
newGetEncryptionConfig ::
  GetEncryptionConfig
newGetEncryptionConfig :: GetEncryptionConfig
newGetEncryptionConfig = GetEncryptionConfig
GetEncryptionConfig'

instance Core.AWSRequest GetEncryptionConfig where
  type
    AWSResponse GetEncryptionConfig =
      GetEncryptionConfigResponse
  request :: (Service -> Service)
-> GetEncryptionConfig -> Request GetEncryptionConfig
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 GetEncryptionConfig
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetEncryptionConfig)))
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 EncryptionConfig -> Int -> GetEncryptionConfigResponse
GetEncryptionConfigResponse'
            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
"EncryptionConfig")
            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 GetEncryptionConfig where
  hashWithSalt :: Int -> GetEncryptionConfig -> Int
hashWithSalt Int
_salt GetEncryptionConfig
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

instance Prelude.NFData GetEncryptionConfig where
  rnf :: GetEncryptionConfig -> ()
rnf GetEncryptionConfig
_ = ()

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

instance Data.ToJSON GetEncryptionConfig where
  toJSON :: GetEncryptionConfig -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

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

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

-- |
-- Create a value of 'GetEncryptionConfigResponse' 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:
--
-- 'encryptionConfig', 'getEncryptionConfigResponse_encryptionConfig' - The encryption configuration document.
--
-- 'httpStatus', 'getEncryptionConfigResponse_httpStatus' - The response's http status code.
newGetEncryptionConfigResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetEncryptionConfigResponse
newGetEncryptionConfigResponse :: Int -> GetEncryptionConfigResponse
newGetEncryptionConfigResponse Int
pHttpStatus_ =
  GetEncryptionConfigResponse'
    { $sel:encryptionConfig:GetEncryptionConfigResponse' :: Maybe EncryptionConfig
encryptionConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetEncryptionConfigResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The encryption configuration document.
getEncryptionConfigResponse_encryptionConfig :: Lens.Lens' GetEncryptionConfigResponse (Prelude.Maybe EncryptionConfig)
getEncryptionConfigResponse_encryptionConfig :: Lens' GetEncryptionConfigResponse (Maybe EncryptionConfig)
getEncryptionConfigResponse_encryptionConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEncryptionConfigResponse' {Maybe EncryptionConfig
encryptionConfig :: Maybe EncryptionConfig
$sel:encryptionConfig:GetEncryptionConfigResponse' :: GetEncryptionConfigResponse -> Maybe EncryptionConfig
encryptionConfig} -> Maybe EncryptionConfig
encryptionConfig) (\s :: GetEncryptionConfigResponse
s@GetEncryptionConfigResponse' {} Maybe EncryptionConfig
a -> GetEncryptionConfigResponse
s {$sel:encryptionConfig:GetEncryptionConfigResponse' :: Maybe EncryptionConfig
encryptionConfig = Maybe EncryptionConfig
a} :: GetEncryptionConfigResponse)

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

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