{-# 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.CloudHSM.GetConfig
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This is documentation for __AWS CloudHSM Classic__. For more
-- information, see
-- <http://aws.amazon.com/cloudhsm/faqs-classic/ AWS CloudHSM Classic FAQs>,
-- the
-- <https://docs.aws.amazon.com/cloudhsm/classic/userguide/ AWS CloudHSM Classic User Guide>,
-- and the
-- <https://docs.aws.amazon.com/cloudhsm/classic/APIReference/ AWS CloudHSM Classic API Reference>.
--
-- __For information about the current version of AWS CloudHSM__, see
-- <http://aws.amazon.com/cloudhsm/ AWS CloudHSM>, the
-- <https://docs.aws.amazon.com/cloudhsm/latest/userguide/ AWS CloudHSM User Guide>,
-- and the
-- <https://docs.aws.amazon.com/cloudhsm/latest/APIReference/ AWS CloudHSM API Reference>.
--
-- Gets the configuration files necessary to connect to all high
-- availability partition groups the client is associated with.
module Amazonka.CloudHSM.GetConfig
  ( -- * Creating a Request
    GetConfig (..),
    newGetConfig,

    -- * Request Lenses
    getConfig_clientArn,
    getConfig_clientVersion,
    getConfig_hapgList,

    -- * Destructuring the Response
    GetConfigResponse (..),
    newGetConfigResponse,

    -- * Response Lenses
    getConfigResponse_configCred,
    getConfigResponse_configFile,
    getConfigResponse_configType,
    getConfigResponse_httpStatus,
  )
where

import Amazonka.CloudHSM.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:/ 'newGetConfig' smart constructor.
data GetConfig = GetConfig'
  { -- | The ARN of the client.
    GetConfig -> Text
clientArn :: Prelude.Text,
    -- | The client version.
    GetConfig -> ClientVersion
clientVersion :: ClientVersion,
    -- | A list of ARNs that identify the high-availability partition groups that
    -- are associated with the client.
    GetConfig -> [Text]
hapgList :: [Prelude.Text]
  }
  deriving (GetConfig -> GetConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetConfig -> GetConfig -> Bool
$c/= :: GetConfig -> GetConfig -> Bool
== :: GetConfig -> GetConfig -> Bool
$c== :: GetConfig -> GetConfig -> Bool
Prelude.Eq, ReadPrec [GetConfig]
ReadPrec GetConfig
Int -> ReadS GetConfig
ReadS [GetConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetConfig]
$creadListPrec :: ReadPrec [GetConfig]
readPrec :: ReadPrec GetConfig
$creadPrec :: ReadPrec GetConfig
readList :: ReadS [GetConfig]
$creadList :: ReadS [GetConfig]
readsPrec :: Int -> ReadS GetConfig
$creadsPrec :: Int -> ReadS GetConfig
Prelude.Read, Int -> GetConfig -> ShowS
[GetConfig] -> ShowS
GetConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetConfig] -> ShowS
$cshowList :: [GetConfig] -> ShowS
show :: GetConfig -> String
$cshow :: GetConfig -> String
showsPrec :: Int -> GetConfig -> ShowS
$cshowsPrec :: Int -> GetConfig -> ShowS
Prelude.Show, forall x. Rep GetConfig x -> GetConfig
forall x. GetConfig -> Rep GetConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetConfig x -> GetConfig
$cfrom :: forall x. GetConfig -> Rep GetConfig x
Prelude.Generic)

-- |
-- Create a value of 'GetConfig' 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:
--
-- 'clientArn', 'getConfig_clientArn' - The ARN of the client.
--
-- 'clientVersion', 'getConfig_clientVersion' - The client version.
--
-- 'hapgList', 'getConfig_hapgList' - A list of ARNs that identify the high-availability partition groups that
-- are associated with the client.
newGetConfig ::
  -- | 'clientArn'
  Prelude.Text ->
  -- | 'clientVersion'
  ClientVersion ->
  GetConfig
newGetConfig :: Text -> ClientVersion -> GetConfig
newGetConfig Text
pClientArn_ ClientVersion
pClientVersion_ =
  GetConfig'
    { $sel:clientArn:GetConfig' :: Text
clientArn = Text
pClientArn_,
      $sel:clientVersion:GetConfig' :: ClientVersion
clientVersion = ClientVersion
pClientVersion_,
      $sel:hapgList:GetConfig' :: [Text]
hapgList = forall a. Monoid a => a
Prelude.mempty
    }

-- | The ARN of the client.
getConfig_clientArn :: Lens.Lens' GetConfig Prelude.Text
getConfig_clientArn :: Lens' GetConfig Text
getConfig_clientArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConfig' {Text
clientArn :: Text
$sel:clientArn:GetConfig' :: GetConfig -> Text
clientArn} -> Text
clientArn) (\s :: GetConfig
s@GetConfig' {} Text
a -> GetConfig
s {$sel:clientArn:GetConfig' :: Text
clientArn = Text
a} :: GetConfig)

-- | The client version.
getConfig_clientVersion :: Lens.Lens' GetConfig ClientVersion
getConfig_clientVersion :: Lens' GetConfig ClientVersion
getConfig_clientVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConfig' {ClientVersion
clientVersion :: ClientVersion
$sel:clientVersion:GetConfig' :: GetConfig -> ClientVersion
clientVersion} -> ClientVersion
clientVersion) (\s :: GetConfig
s@GetConfig' {} ClientVersion
a -> GetConfig
s {$sel:clientVersion:GetConfig' :: ClientVersion
clientVersion = ClientVersion
a} :: GetConfig)

-- | A list of ARNs that identify the high-availability partition groups that
-- are associated with the client.
getConfig_hapgList :: Lens.Lens' GetConfig [Prelude.Text]
getConfig_hapgList :: Lens' GetConfig [Text]
getConfig_hapgList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConfig' {[Text]
hapgList :: [Text]
$sel:hapgList:GetConfig' :: GetConfig -> [Text]
hapgList} -> [Text]
hapgList) (\s :: GetConfig
s@GetConfig' {} [Text]
a -> GetConfig
s {$sel:hapgList:GetConfig' :: [Text]
hapgList = [Text]
a} :: GetConfig) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest GetConfig where
  type AWSResponse GetConfig = GetConfigResponse
  request :: (Service -> Service) -> GetConfig -> Request GetConfig
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 GetConfig
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetConfig)))
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 Text -> Maybe Text -> Int -> GetConfigResponse
GetConfigResponse'
            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
"ConfigCred")
            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
"ConfigFile")
            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
"ConfigType")
            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 GetConfig where
  hashWithSalt :: Int -> GetConfig -> Int
hashWithSalt Int
_salt GetConfig' {[Text]
Text
ClientVersion
hapgList :: [Text]
clientVersion :: ClientVersion
clientArn :: Text
$sel:hapgList:GetConfig' :: GetConfig -> [Text]
$sel:clientVersion:GetConfig' :: GetConfig -> ClientVersion
$sel:clientArn:GetConfig' :: GetConfig -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ClientVersion
clientVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
hapgList

instance Prelude.NFData GetConfig where
  rnf :: GetConfig -> ()
rnf GetConfig' {[Text]
Text
ClientVersion
hapgList :: [Text]
clientVersion :: ClientVersion
clientArn :: Text
$sel:hapgList:GetConfig' :: GetConfig -> [Text]
$sel:clientVersion:GetConfig' :: GetConfig -> ClientVersion
$sel:clientArn:GetConfig' :: GetConfig -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
clientArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ClientVersion
clientVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
hapgList

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

instance Data.ToJSON GetConfig where
  toJSON :: GetConfig -> Value
toJSON GetConfig' {[Text]
Text
ClientVersion
hapgList :: [Text]
clientVersion :: ClientVersion
clientArn :: Text
$sel:hapgList:GetConfig' :: GetConfig -> [Text]
$sel:clientVersion:GetConfig' :: GetConfig -> ClientVersion
$sel:clientArn:GetConfig' :: GetConfig -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"ClientArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clientArn),
            forall a. a -> Maybe a
Prelude.Just (Key
"ClientVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ClientVersion
clientVersion),
            forall a. a -> Maybe a
Prelude.Just (Key
"HapgList" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
hapgList)
          ]
      )

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

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

-- | /See:/ 'newGetConfigResponse' smart constructor.
data GetConfigResponse = GetConfigResponse'
  { -- | The certificate file containing the server.pem files of the HSMs.
    GetConfigResponse -> Maybe Text
configCred :: Prelude.Maybe Prelude.Text,
    -- | The chrystoki.conf configuration file.
    GetConfigResponse -> Maybe Text
configFile :: Prelude.Maybe Prelude.Text,
    -- | The type of credentials.
    GetConfigResponse -> Maybe Text
configType :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetConfigResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetConfigResponse -> GetConfigResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetConfigResponse -> GetConfigResponse -> Bool
$c/= :: GetConfigResponse -> GetConfigResponse -> Bool
== :: GetConfigResponse -> GetConfigResponse -> Bool
$c== :: GetConfigResponse -> GetConfigResponse -> Bool
Prelude.Eq, ReadPrec [GetConfigResponse]
ReadPrec GetConfigResponse
Int -> ReadS GetConfigResponse
ReadS [GetConfigResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetConfigResponse]
$creadListPrec :: ReadPrec [GetConfigResponse]
readPrec :: ReadPrec GetConfigResponse
$creadPrec :: ReadPrec GetConfigResponse
readList :: ReadS [GetConfigResponse]
$creadList :: ReadS [GetConfigResponse]
readsPrec :: Int -> ReadS GetConfigResponse
$creadsPrec :: Int -> ReadS GetConfigResponse
Prelude.Read, Int -> GetConfigResponse -> ShowS
[GetConfigResponse] -> ShowS
GetConfigResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetConfigResponse] -> ShowS
$cshowList :: [GetConfigResponse] -> ShowS
show :: GetConfigResponse -> String
$cshow :: GetConfigResponse -> String
showsPrec :: Int -> GetConfigResponse -> ShowS
$cshowsPrec :: Int -> GetConfigResponse -> ShowS
Prelude.Show, forall x. Rep GetConfigResponse x -> GetConfigResponse
forall x. GetConfigResponse -> Rep GetConfigResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetConfigResponse x -> GetConfigResponse
$cfrom :: forall x. GetConfigResponse -> Rep GetConfigResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetConfigResponse' 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:
--
-- 'configCred', 'getConfigResponse_configCred' - The certificate file containing the server.pem files of the HSMs.
--
-- 'configFile', 'getConfigResponse_configFile' - The chrystoki.conf configuration file.
--
-- 'configType', 'getConfigResponse_configType' - The type of credentials.
--
-- 'httpStatus', 'getConfigResponse_httpStatus' - The response's http status code.
newGetConfigResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetConfigResponse
newGetConfigResponse :: Int -> GetConfigResponse
newGetConfigResponse Int
pHttpStatus_ =
  GetConfigResponse'
    { $sel:configCred:GetConfigResponse' :: Maybe Text
configCred = forall a. Maybe a
Prelude.Nothing,
      $sel:configFile:GetConfigResponse' :: Maybe Text
configFile = forall a. Maybe a
Prelude.Nothing,
      $sel:configType:GetConfigResponse' :: Maybe Text
configType = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetConfigResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The certificate file containing the server.pem files of the HSMs.
getConfigResponse_configCred :: Lens.Lens' GetConfigResponse (Prelude.Maybe Prelude.Text)
getConfigResponse_configCred :: Lens' GetConfigResponse (Maybe Text)
getConfigResponse_configCred = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConfigResponse' {Maybe Text
configCred :: Maybe Text
$sel:configCred:GetConfigResponse' :: GetConfigResponse -> Maybe Text
configCred} -> Maybe Text
configCred) (\s :: GetConfigResponse
s@GetConfigResponse' {} Maybe Text
a -> GetConfigResponse
s {$sel:configCred:GetConfigResponse' :: Maybe Text
configCred = Maybe Text
a} :: GetConfigResponse)

-- | The chrystoki.conf configuration file.
getConfigResponse_configFile :: Lens.Lens' GetConfigResponse (Prelude.Maybe Prelude.Text)
getConfigResponse_configFile :: Lens' GetConfigResponse (Maybe Text)
getConfigResponse_configFile = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConfigResponse' {Maybe Text
configFile :: Maybe Text
$sel:configFile:GetConfigResponse' :: GetConfigResponse -> Maybe Text
configFile} -> Maybe Text
configFile) (\s :: GetConfigResponse
s@GetConfigResponse' {} Maybe Text
a -> GetConfigResponse
s {$sel:configFile:GetConfigResponse' :: Maybe Text
configFile = Maybe Text
a} :: GetConfigResponse)

-- | The type of credentials.
getConfigResponse_configType :: Lens.Lens' GetConfigResponse (Prelude.Maybe Prelude.Text)
getConfigResponse_configType :: Lens' GetConfigResponse (Maybe Text)
getConfigResponse_configType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConfigResponse' {Maybe Text
configType :: Maybe Text
$sel:configType:GetConfigResponse' :: GetConfigResponse -> Maybe Text
configType} -> Maybe Text
configType) (\s :: GetConfigResponse
s@GetConfigResponse' {} Maybe Text
a -> GetConfigResponse
s {$sel:configType:GetConfigResponse' :: Maybe Text
configType = Maybe Text
a} :: GetConfigResponse)

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

instance Prelude.NFData GetConfigResponse where
  rnf :: GetConfigResponse -> ()
rnf GetConfigResponse' {Int
Maybe Text
httpStatus :: Int
configType :: Maybe Text
configFile :: Maybe Text
configCred :: Maybe Text
$sel:httpStatus:GetConfigResponse' :: GetConfigResponse -> Int
$sel:configType:GetConfigResponse' :: GetConfigResponse -> Maybe Text
$sel:configFile:GetConfigResponse' :: GetConfigResponse -> Maybe Text
$sel:configCred:GetConfigResponse' :: GetConfigResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
configCred
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
configFile
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
configType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus