{-# 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.StorageGateway.UpdateChapCredentials
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the Challenge-Handshake Authentication Protocol (CHAP)
-- credentials for a specified iSCSI target. By default, a gateway does not
-- have CHAP enabled; however, for added security, you might use it. This
-- operation is supported in the volume and tape gateway types.
--
-- When you update CHAP credentials, all existing connections on the target
-- are closed and initiators must reconnect with the new credentials.
module Amazonka.StorageGateway.UpdateChapCredentials
  ( -- * Creating a Request
    UpdateChapCredentials (..),
    newUpdateChapCredentials,

    -- * Request Lenses
    updateChapCredentials_secretToAuthenticateTarget,
    updateChapCredentials_targetARN,
    updateChapCredentials_secretToAuthenticateInitiator,
    updateChapCredentials_initiatorName,

    -- * Destructuring the Response
    UpdateChapCredentialsResponse (..),
    newUpdateChapCredentialsResponse,

    -- * Response Lenses
    updateChapCredentialsResponse_initiatorName,
    updateChapCredentialsResponse_targetARN,
    updateChapCredentialsResponse_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.StorageGateway.Types

-- | A JSON object containing one or more of the following fields:
--
-- -   UpdateChapCredentialsInput$InitiatorName
--
-- -   UpdateChapCredentialsInput$SecretToAuthenticateInitiator
--
-- -   UpdateChapCredentialsInput$SecretToAuthenticateTarget
--
-- -   UpdateChapCredentialsInput$TargetARN
--
-- /See:/ 'newUpdateChapCredentials' smart constructor.
data UpdateChapCredentials = UpdateChapCredentials'
  { -- | The secret key that the target must provide to participate in mutual
    -- CHAP with the initiator (e.g. Windows client).
    --
    -- Byte constraints: Minimum bytes of 12. Maximum bytes of 16.
    --
    -- The secret key must be between 12 and 16 bytes when encoded in UTF-8.
    UpdateChapCredentials -> Maybe (Sensitive Text)
secretToAuthenticateTarget :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The Amazon Resource Name (ARN) of the iSCSI volume target. Use the
    -- DescribeStorediSCSIVolumes operation to return the TargetARN for
    -- specified VolumeARN.
    UpdateChapCredentials -> Text
targetARN :: Prelude.Text,
    -- | The secret key that the initiator (for example, the Windows client) must
    -- provide to participate in mutual CHAP with the target.
    --
    -- The secret key must be between 12 and 16 bytes when encoded in UTF-8.
    UpdateChapCredentials -> Sensitive Text
secretToAuthenticateInitiator :: Data.Sensitive Prelude.Text,
    -- | The iSCSI initiator that connects to the target.
    UpdateChapCredentials -> Text
initiatorName :: Prelude.Text
  }
  deriving (UpdateChapCredentials -> UpdateChapCredentials -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateChapCredentials -> UpdateChapCredentials -> Bool
$c/= :: UpdateChapCredentials -> UpdateChapCredentials -> Bool
== :: UpdateChapCredentials -> UpdateChapCredentials -> Bool
$c== :: UpdateChapCredentials -> UpdateChapCredentials -> Bool
Prelude.Eq, Int -> UpdateChapCredentials -> ShowS
[UpdateChapCredentials] -> ShowS
UpdateChapCredentials -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateChapCredentials] -> ShowS
$cshowList :: [UpdateChapCredentials] -> ShowS
show :: UpdateChapCredentials -> String
$cshow :: UpdateChapCredentials -> String
showsPrec :: Int -> UpdateChapCredentials -> ShowS
$cshowsPrec :: Int -> UpdateChapCredentials -> ShowS
Prelude.Show, forall x. Rep UpdateChapCredentials x -> UpdateChapCredentials
forall x. UpdateChapCredentials -> Rep UpdateChapCredentials x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateChapCredentials x -> UpdateChapCredentials
$cfrom :: forall x. UpdateChapCredentials -> Rep UpdateChapCredentials x
Prelude.Generic)

-- |
-- Create a value of 'UpdateChapCredentials' 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:
--
-- 'secretToAuthenticateTarget', 'updateChapCredentials_secretToAuthenticateTarget' - The secret key that the target must provide to participate in mutual
-- CHAP with the initiator (e.g. Windows client).
--
-- Byte constraints: Minimum bytes of 12. Maximum bytes of 16.
--
-- The secret key must be between 12 and 16 bytes when encoded in UTF-8.
--
-- 'targetARN', 'updateChapCredentials_targetARN' - The Amazon Resource Name (ARN) of the iSCSI volume target. Use the
-- DescribeStorediSCSIVolumes operation to return the TargetARN for
-- specified VolumeARN.
--
-- 'secretToAuthenticateInitiator', 'updateChapCredentials_secretToAuthenticateInitiator' - The secret key that the initiator (for example, the Windows client) must
-- provide to participate in mutual CHAP with the target.
--
-- The secret key must be between 12 and 16 bytes when encoded in UTF-8.
--
-- 'initiatorName', 'updateChapCredentials_initiatorName' - The iSCSI initiator that connects to the target.
newUpdateChapCredentials ::
  -- | 'targetARN'
  Prelude.Text ->
  -- | 'secretToAuthenticateInitiator'
  Prelude.Text ->
  -- | 'initiatorName'
  Prelude.Text ->
  UpdateChapCredentials
newUpdateChapCredentials :: Text -> Text -> Text -> UpdateChapCredentials
newUpdateChapCredentials
  Text
pTargetARN_
  Text
pSecretToAuthenticateInitiator_
  Text
pInitiatorName_ =
    UpdateChapCredentials'
      { $sel:secretToAuthenticateTarget:UpdateChapCredentials' :: Maybe (Sensitive Text)
secretToAuthenticateTarget =
          forall a. Maybe a
Prelude.Nothing,
        $sel:targetARN:UpdateChapCredentials' :: Text
targetARN = Text
pTargetARN_,
        $sel:secretToAuthenticateInitiator:UpdateChapCredentials' :: Sensitive Text
secretToAuthenticateInitiator =
          forall a. Iso' (Sensitive a) a
Data._Sensitive
            forall t b. AReview t b -> b -> t
Lens.# Text
pSecretToAuthenticateInitiator_,
        $sel:initiatorName:UpdateChapCredentials' :: Text
initiatorName = Text
pInitiatorName_
      }

-- | The secret key that the target must provide to participate in mutual
-- CHAP with the initiator (e.g. Windows client).
--
-- Byte constraints: Minimum bytes of 12. Maximum bytes of 16.
--
-- The secret key must be between 12 and 16 bytes when encoded in UTF-8.
updateChapCredentials_secretToAuthenticateTarget :: Lens.Lens' UpdateChapCredentials (Prelude.Maybe Prelude.Text)
updateChapCredentials_secretToAuthenticateTarget :: Lens' UpdateChapCredentials (Maybe Text)
updateChapCredentials_secretToAuthenticateTarget = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChapCredentials' {Maybe (Sensitive Text)
secretToAuthenticateTarget :: Maybe (Sensitive Text)
$sel:secretToAuthenticateTarget:UpdateChapCredentials' :: UpdateChapCredentials -> Maybe (Sensitive Text)
secretToAuthenticateTarget} -> Maybe (Sensitive Text)
secretToAuthenticateTarget) (\s :: UpdateChapCredentials
s@UpdateChapCredentials' {} Maybe (Sensitive Text)
a -> UpdateChapCredentials
s {$sel:secretToAuthenticateTarget:UpdateChapCredentials' :: Maybe (Sensitive Text)
secretToAuthenticateTarget = Maybe (Sensitive Text)
a} :: UpdateChapCredentials) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The Amazon Resource Name (ARN) of the iSCSI volume target. Use the
-- DescribeStorediSCSIVolumes operation to return the TargetARN for
-- specified VolumeARN.
updateChapCredentials_targetARN :: Lens.Lens' UpdateChapCredentials Prelude.Text
updateChapCredentials_targetARN :: Lens' UpdateChapCredentials Text
updateChapCredentials_targetARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChapCredentials' {Text
targetARN :: Text
$sel:targetARN:UpdateChapCredentials' :: UpdateChapCredentials -> Text
targetARN} -> Text
targetARN) (\s :: UpdateChapCredentials
s@UpdateChapCredentials' {} Text
a -> UpdateChapCredentials
s {$sel:targetARN:UpdateChapCredentials' :: Text
targetARN = Text
a} :: UpdateChapCredentials)

-- | The secret key that the initiator (for example, the Windows client) must
-- provide to participate in mutual CHAP with the target.
--
-- The secret key must be between 12 and 16 bytes when encoded in UTF-8.
updateChapCredentials_secretToAuthenticateInitiator :: Lens.Lens' UpdateChapCredentials Prelude.Text
updateChapCredentials_secretToAuthenticateInitiator :: Lens' UpdateChapCredentials Text
updateChapCredentials_secretToAuthenticateInitiator = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChapCredentials' {Sensitive Text
secretToAuthenticateInitiator :: Sensitive Text
$sel:secretToAuthenticateInitiator:UpdateChapCredentials' :: UpdateChapCredentials -> Sensitive Text
secretToAuthenticateInitiator} -> Sensitive Text
secretToAuthenticateInitiator) (\s :: UpdateChapCredentials
s@UpdateChapCredentials' {} Sensitive Text
a -> UpdateChapCredentials
s {$sel:secretToAuthenticateInitiator:UpdateChapCredentials' :: Sensitive Text
secretToAuthenticateInitiator = Sensitive Text
a} :: UpdateChapCredentials) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The iSCSI initiator that connects to the target.
updateChapCredentials_initiatorName :: Lens.Lens' UpdateChapCredentials Prelude.Text
updateChapCredentials_initiatorName :: Lens' UpdateChapCredentials Text
updateChapCredentials_initiatorName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChapCredentials' {Text
initiatorName :: Text
$sel:initiatorName:UpdateChapCredentials' :: UpdateChapCredentials -> Text
initiatorName} -> Text
initiatorName) (\s :: UpdateChapCredentials
s@UpdateChapCredentials' {} Text
a -> UpdateChapCredentials
s {$sel:initiatorName:UpdateChapCredentials' :: Text
initiatorName = Text
a} :: UpdateChapCredentials)

instance Core.AWSRequest UpdateChapCredentials where
  type
    AWSResponse UpdateChapCredentials =
      UpdateChapCredentialsResponse
  request :: (Service -> Service)
-> UpdateChapCredentials -> Request UpdateChapCredentials
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 UpdateChapCredentials
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateChapCredentials)))
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 -> Int -> UpdateChapCredentialsResponse
UpdateChapCredentialsResponse'
            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
"InitiatorName")
            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
"TargetARN")
            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 UpdateChapCredentials where
  hashWithSalt :: Int -> UpdateChapCredentials -> Int
hashWithSalt Int
_salt UpdateChapCredentials' {Maybe (Sensitive Text)
Text
Sensitive Text
initiatorName :: Text
secretToAuthenticateInitiator :: Sensitive Text
targetARN :: Text
secretToAuthenticateTarget :: Maybe (Sensitive Text)
$sel:initiatorName:UpdateChapCredentials' :: UpdateChapCredentials -> Text
$sel:secretToAuthenticateInitiator:UpdateChapCredentials' :: UpdateChapCredentials -> Sensitive Text
$sel:targetARN:UpdateChapCredentials' :: UpdateChapCredentials -> Text
$sel:secretToAuthenticateTarget:UpdateChapCredentials' :: UpdateChapCredentials -> Maybe (Sensitive Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
secretToAuthenticateTarget
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
targetARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
secretToAuthenticateInitiator
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
initiatorName

instance Prelude.NFData UpdateChapCredentials where
  rnf :: UpdateChapCredentials -> ()
rnf UpdateChapCredentials' {Maybe (Sensitive Text)
Text
Sensitive Text
initiatorName :: Text
secretToAuthenticateInitiator :: Sensitive Text
targetARN :: Text
secretToAuthenticateTarget :: Maybe (Sensitive Text)
$sel:initiatorName:UpdateChapCredentials' :: UpdateChapCredentials -> Text
$sel:secretToAuthenticateInitiator:UpdateChapCredentials' :: UpdateChapCredentials -> Sensitive Text
$sel:targetARN:UpdateChapCredentials' :: UpdateChapCredentials -> Text
$sel:secretToAuthenticateTarget:UpdateChapCredentials' :: UpdateChapCredentials -> Maybe (Sensitive Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
secretToAuthenticateTarget
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
targetARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
secretToAuthenticateInitiator
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
initiatorName

instance Data.ToHeaders UpdateChapCredentials where
  toHeaders :: UpdateChapCredentials -> 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
"StorageGateway_20130630.UpdateChapCredentials" ::
                          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 UpdateChapCredentials where
  toJSON :: UpdateChapCredentials -> Value
toJSON UpdateChapCredentials' {Maybe (Sensitive Text)
Text
Sensitive Text
initiatorName :: Text
secretToAuthenticateInitiator :: Sensitive Text
targetARN :: Text
secretToAuthenticateTarget :: Maybe (Sensitive Text)
$sel:initiatorName:UpdateChapCredentials' :: UpdateChapCredentials -> Text
$sel:secretToAuthenticateInitiator:UpdateChapCredentials' :: UpdateChapCredentials -> Sensitive Text
$sel:targetARN:UpdateChapCredentials' :: UpdateChapCredentials -> Text
$sel:secretToAuthenticateTarget:UpdateChapCredentials' :: UpdateChapCredentials -> Maybe (Sensitive Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"SecretToAuthenticateTarget" 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 (Sensitive Text)
secretToAuthenticateTarget,
            forall a. a -> Maybe a
Prelude.Just (Key
"TargetARN" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
targetARN),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"SecretToAuthenticateInitiator"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
secretToAuthenticateInitiator
              ),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"InitiatorName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
initiatorName)
          ]
      )

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

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

-- | A JSON object containing the following fields:
--
-- /See:/ 'newUpdateChapCredentialsResponse' smart constructor.
data UpdateChapCredentialsResponse = UpdateChapCredentialsResponse'
  { -- | The iSCSI initiator that connects to the target. This is the same
    -- initiator name specified in the request.
    UpdateChapCredentialsResponse -> Maybe Text
initiatorName :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the target. This is the same target
    -- specified in the request.
    UpdateChapCredentialsResponse -> Maybe Text
targetARN :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateChapCredentialsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateChapCredentialsResponse
-> UpdateChapCredentialsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateChapCredentialsResponse
-> UpdateChapCredentialsResponse -> Bool
$c/= :: UpdateChapCredentialsResponse
-> UpdateChapCredentialsResponse -> Bool
== :: UpdateChapCredentialsResponse
-> UpdateChapCredentialsResponse -> Bool
$c== :: UpdateChapCredentialsResponse
-> UpdateChapCredentialsResponse -> Bool
Prelude.Eq, ReadPrec [UpdateChapCredentialsResponse]
ReadPrec UpdateChapCredentialsResponse
Int -> ReadS UpdateChapCredentialsResponse
ReadS [UpdateChapCredentialsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateChapCredentialsResponse]
$creadListPrec :: ReadPrec [UpdateChapCredentialsResponse]
readPrec :: ReadPrec UpdateChapCredentialsResponse
$creadPrec :: ReadPrec UpdateChapCredentialsResponse
readList :: ReadS [UpdateChapCredentialsResponse]
$creadList :: ReadS [UpdateChapCredentialsResponse]
readsPrec :: Int -> ReadS UpdateChapCredentialsResponse
$creadsPrec :: Int -> ReadS UpdateChapCredentialsResponse
Prelude.Read, Int -> UpdateChapCredentialsResponse -> ShowS
[UpdateChapCredentialsResponse] -> ShowS
UpdateChapCredentialsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateChapCredentialsResponse] -> ShowS
$cshowList :: [UpdateChapCredentialsResponse] -> ShowS
show :: UpdateChapCredentialsResponse -> String
$cshow :: UpdateChapCredentialsResponse -> String
showsPrec :: Int -> UpdateChapCredentialsResponse -> ShowS
$cshowsPrec :: Int -> UpdateChapCredentialsResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateChapCredentialsResponse x
-> UpdateChapCredentialsResponse
forall x.
UpdateChapCredentialsResponse
-> Rep UpdateChapCredentialsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateChapCredentialsResponse x
-> UpdateChapCredentialsResponse
$cfrom :: forall x.
UpdateChapCredentialsResponse
-> Rep UpdateChapCredentialsResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateChapCredentialsResponse' 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:
--
-- 'initiatorName', 'updateChapCredentialsResponse_initiatorName' - The iSCSI initiator that connects to the target. This is the same
-- initiator name specified in the request.
--
-- 'targetARN', 'updateChapCredentialsResponse_targetARN' - The Amazon Resource Name (ARN) of the target. This is the same target
-- specified in the request.
--
-- 'httpStatus', 'updateChapCredentialsResponse_httpStatus' - The response's http status code.
newUpdateChapCredentialsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateChapCredentialsResponse
newUpdateChapCredentialsResponse :: Int -> UpdateChapCredentialsResponse
newUpdateChapCredentialsResponse Int
pHttpStatus_ =
  UpdateChapCredentialsResponse'
    { $sel:initiatorName:UpdateChapCredentialsResponse' :: Maybe Text
initiatorName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:targetARN:UpdateChapCredentialsResponse' :: Maybe Text
targetARN = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateChapCredentialsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The iSCSI initiator that connects to the target. This is the same
-- initiator name specified in the request.
updateChapCredentialsResponse_initiatorName :: Lens.Lens' UpdateChapCredentialsResponse (Prelude.Maybe Prelude.Text)
updateChapCredentialsResponse_initiatorName :: Lens' UpdateChapCredentialsResponse (Maybe Text)
updateChapCredentialsResponse_initiatorName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChapCredentialsResponse' {Maybe Text
initiatorName :: Maybe Text
$sel:initiatorName:UpdateChapCredentialsResponse' :: UpdateChapCredentialsResponse -> Maybe Text
initiatorName} -> Maybe Text
initiatorName) (\s :: UpdateChapCredentialsResponse
s@UpdateChapCredentialsResponse' {} Maybe Text
a -> UpdateChapCredentialsResponse
s {$sel:initiatorName:UpdateChapCredentialsResponse' :: Maybe Text
initiatorName = Maybe Text
a} :: UpdateChapCredentialsResponse)

-- | The Amazon Resource Name (ARN) of the target. This is the same target
-- specified in the request.
updateChapCredentialsResponse_targetARN :: Lens.Lens' UpdateChapCredentialsResponse (Prelude.Maybe Prelude.Text)
updateChapCredentialsResponse_targetARN :: Lens' UpdateChapCredentialsResponse (Maybe Text)
updateChapCredentialsResponse_targetARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChapCredentialsResponse' {Maybe Text
targetARN :: Maybe Text
$sel:targetARN:UpdateChapCredentialsResponse' :: UpdateChapCredentialsResponse -> Maybe Text
targetARN} -> Maybe Text
targetARN) (\s :: UpdateChapCredentialsResponse
s@UpdateChapCredentialsResponse' {} Maybe Text
a -> UpdateChapCredentialsResponse
s {$sel:targetARN:UpdateChapCredentialsResponse' :: Maybe Text
targetARN = Maybe Text
a} :: UpdateChapCredentialsResponse)

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

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