{-# 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.CreateLunaClient
-- 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>.
--
-- Creates an HSM client.
module Amazonka.CloudHSM.CreateLunaClient
  ( -- * Creating a Request
    CreateLunaClient (..),
    newCreateLunaClient,

    -- * Request Lenses
    createLunaClient_label,
    createLunaClient_certificate,

    -- * Destructuring the Response
    CreateLunaClientResponse (..),
    newCreateLunaClientResponse,

    -- * Response Lenses
    createLunaClientResponse_clientArn,
    createLunaClientResponse_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

-- | Contains the inputs for the CreateLunaClient action.
--
-- /See:/ 'newCreateLunaClient' smart constructor.
data CreateLunaClient = CreateLunaClient'
  { -- | The label for the client.
    CreateLunaClient -> Maybe Text
label :: Prelude.Maybe Prelude.Text,
    -- | The contents of a Base64-Encoded X.509 v3 certificate to be installed on
    -- the HSMs used by this client.
    CreateLunaClient -> Text
certificate :: Prelude.Text
  }
  deriving (CreateLunaClient -> CreateLunaClient -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateLunaClient -> CreateLunaClient -> Bool
$c/= :: CreateLunaClient -> CreateLunaClient -> Bool
== :: CreateLunaClient -> CreateLunaClient -> Bool
$c== :: CreateLunaClient -> CreateLunaClient -> Bool
Prelude.Eq, ReadPrec [CreateLunaClient]
ReadPrec CreateLunaClient
Int -> ReadS CreateLunaClient
ReadS [CreateLunaClient]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateLunaClient]
$creadListPrec :: ReadPrec [CreateLunaClient]
readPrec :: ReadPrec CreateLunaClient
$creadPrec :: ReadPrec CreateLunaClient
readList :: ReadS [CreateLunaClient]
$creadList :: ReadS [CreateLunaClient]
readsPrec :: Int -> ReadS CreateLunaClient
$creadsPrec :: Int -> ReadS CreateLunaClient
Prelude.Read, Int -> CreateLunaClient -> ShowS
[CreateLunaClient] -> ShowS
CreateLunaClient -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateLunaClient] -> ShowS
$cshowList :: [CreateLunaClient] -> ShowS
show :: CreateLunaClient -> String
$cshow :: CreateLunaClient -> String
showsPrec :: Int -> CreateLunaClient -> ShowS
$cshowsPrec :: Int -> CreateLunaClient -> ShowS
Prelude.Show, forall x. Rep CreateLunaClient x -> CreateLunaClient
forall x. CreateLunaClient -> Rep CreateLunaClient x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateLunaClient x -> CreateLunaClient
$cfrom :: forall x. CreateLunaClient -> Rep CreateLunaClient x
Prelude.Generic)

-- |
-- Create a value of 'CreateLunaClient' 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:
--
-- 'label', 'createLunaClient_label' - The label for the client.
--
-- 'certificate', 'createLunaClient_certificate' - The contents of a Base64-Encoded X.509 v3 certificate to be installed on
-- the HSMs used by this client.
newCreateLunaClient ::
  -- | 'certificate'
  Prelude.Text ->
  CreateLunaClient
newCreateLunaClient :: Text -> CreateLunaClient
newCreateLunaClient Text
pCertificate_ =
  CreateLunaClient'
    { $sel:label:CreateLunaClient' :: Maybe Text
label = forall a. Maybe a
Prelude.Nothing,
      $sel:certificate:CreateLunaClient' :: Text
certificate = Text
pCertificate_
    }

-- | The label for the client.
createLunaClient_label :: Lens.Lens' CreateLunaClient (Prelude.Maybe Prelude.Text)
createLunaClient_label :: Lens' CreateLunaClient (Maybe Text)
createLunaClient_label = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLunaClient' {Maybe Text
label :: Maybe Text
$sel:label:CreateLunaClient' :: CreateLunaClient -> Maybe Text
label} -> Maybe Text
label) (\s :: CreateLunaClient
s@CreateLunaClient' {} Maybe Text
a -> CreateLunaClient
s {$sel:label:CreateLunaClient' :: Maybe Text
label = Maybe Text
a} :: CreateLunaClient)

-- | The contents of a Base64-Encoded X.509 v3 certificate to be installed on
-- the HSMs used by this client.
createLunaClient_certificate :: Lens.Lens' CreateLunaClient Prelude.Text
createLunaClient_certificate :: Lens' CreateLunaClient Text
createLunaClient_certificate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLunaClient' {Text
certificate :: Text
$sel:certificate:CreateLunaClient' :: CreateLunaClient -> Text
certificate} -> Text
certificate) (\s :: CreateLunaClient
s@CreateLunaClient' {} Text
a -> CreateLunaClient
s {$sel:certificate:CreateLunaClient' :: Text
certificate = Text
a} :: CreateLunaClient)

instance Core.AWSRequest CreateLunaClient where
  type
    AWSResponse CreateLunaClient =
      CreateLunaClientResponse
  request :: (Service -> Service)
-> CreateLunaClient -> Request CreateLunaClient
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 CreateLunaClient
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateLunaClient)))
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 -> Int -> CreateLunaClientResponse
CreateLunaClientResponse'
            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
"ClientArn")
            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 CreateLunaClient where
  hashWithSalt :: Int -> CreateLunaClient -> Int
hashWithSalt Int
_salt CreateLunaClient' {Maybe Text
Text
certificate :: Text
label :: Maybe Text
$sel:certificate:CreateLunaClient' :: CreateLunaClient -> Text
$sel:label:CreateLunaClient' :: CreateLunaClient -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
label
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
certificate

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

instance Data.ToHeaders CreateLunaClient where
  toHeaders :: CreateLunaClient -> 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.CreateLunaClient" ::
                          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 CreateLunaClient where
  toJSON :: CreateLunaClient -> Value
toJSON CreateLunaClient' {Maybe Text
Text
certificate :: Text
label :: Maybe Text
$sel:certificate:CreateLunaClient' :: CreateLunaClient -> Text
$sel:label:CreateLunaClient' :: CreateLunaClient -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Label" 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
label,
            forall a. a -> Maybe a
Prelude.Just (Key
"Certificate" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
certificate)
          ]
      )

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

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

-- | Contains the output of the CreateLunaClient action.
--
-- /See:/ 'newCreateLunaClientResponse' smart constructor.
data CreateLunaClientResponse = CreateLunaClientResponse'
  { -- | The ARN of the client.
    CreateLunaClientResponse -> Maybe Text
clientArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateLunaClientResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateLunaClientResponse -> CreateLunaClientResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateLunaClientResponse -> CreateLunaClientResponse -> Bool
$c/= :: CreateLunaClientResponse -> CreateLunaClientResponse -> Bool
== :: CreateLunaClientResponse -> CreateLunaClientResponse -> Bool
$c== :: CreateLunaClientResponse -> CreateLunaClientResponse -> Bool
Prelude.Eq, ReadPrec [CreateLunaClientResponse]
ReadPrec CreateLunaClientResponse
Int -> ReadS CreateLunaClientResponse
ReadS [CreateLunaClientResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateLunaClientResponse]
$creadListPrec :: ReadPrec [CreateLunaClientResponse]
readPrec :: ReadPrec CreateLunaClientResponse
$creadPrec :: ReadPrec CreateLunaClientResponse
readList :: ReadS [CreateLunaClientResponse]
$creadList :: ReadS [CreateLunaClientResponse]
readsPrec :: Int -> ReadS CreateLunaClientResponse
$creadsPrec :: Int -> ReadS CreateLunaClientResponse
Prelude.Read, Int -> CreateLunaClientResponse -> ShowS
[CreateLunaClientResponse] -> ShowS
CreateLunaClientResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateLunaClientResponse] -> ShowS
$cshowList :: [CreateLunaClientResponse] -> ShowS
show :: CreateLunaClientResponse -> String
$cshow :: CreateLunaClientResponse -> String
showsPrec :: Int -> CreateLunaClientResponse -> ShowS
$cshowsPrec :: Int -> CreateLunaClientResponse -> ShowS
Prelude.Show, forall x.
Rep CreateLunaClientResponse x -> CreateLunaClientResponse
forall x.
CreateLunaClientResponse -> Rep CreateLunaClientResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateLunaClientResponse x -> CreateLunaClientResponse
$cfrom :: forall x.
CreateLunaClientResponse -> Rep CreateLunaClientResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateLunaClientResponse' 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', 'createLunaClientResponse_clientArn' - The ARN of the client.
--
-- 'httpStatus', 'createLunaClientResponse_httpStatus' - The response's http status code.
newCreateLunaClientResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateLunaClientResponse
newCreateLunaClientResponse :: Int -> CreateLunaClientResponse
newCreateLunaClientResponse Int
pHttpStatus_ =
  CreateLunaClientResponse'
    { $sel:clientArn:CreateLunaClientResponse' :: Maybe Text
clientArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateLunaClientResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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