{-# 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.IAM.ResetServiceSpecificCredential
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Resets the password for a service-specific credential. The new password
-- is Amazon Web Services generated and cryptographically strong. It cannot
-- be configured by the user. Resetting the password immediately
-- invalidates the previous password associated with this user.
module Amazonka.IAM.ResetServiceSpecificCredential
  ( -- * Creating a Request
    ResetServiceSpecificCredential (..),
    newResetServiceSpecificCredential,

    -- * Request Lenses
    resetServiceSpecificCredential_userName,
    resetServiceSpecificCredential_serviceSpecificCredentialId,

    -- * Destructuring the Response
    ResetServiceSpecificCredentialResponse (..),
    newResetServiceSpecificCredentialResponse,

    -- * Response Lenses
    resetServiceSpecificCredentialResponse_serviceSpecificCredential,
    resetServiceSpecificCredentialResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IAM.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newResetServiceSpecificCredential' smart constructor.
data ResetServiceSpecificCredential = ResetServiceSpecificCredential'
  { -- | The name of the IAM user associated with the service-specific
    -- credential. If this value is not specified, then the operation assumes
    -- the user whose credentials are used to call the operation.
    --
    -- This parameter allows (through its
    -- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
    -- consisting of upper and lowercase alphanumeric characters with no
    -- spaces. You can also include any of the following characters: _+=,.\@-
    ResetServiceSpecificCredential -> Maybe Text
userName :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier of the service-specific credential.
    --
    -- This parameter allows (through its
    -- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
    -- that can consist of any upper or lowercased letter or digit.
    ResetServiceSpecificCredential -> Text
serviceSpecificCredentialId :: Prelude.Text
  }
  deriving (ResetServiceSpecificCredential
-> ResetServiceSpecificCredential -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetServiceSpecificCredential
-> ResetServiceSpecificCredential -> Bool
$c/= :: ResetServiceSpecificCredential
-> ResetServiceSpecificCredential -> Bool
== :: ResetServiceSpecificCredential
-> ResetServiceSpecificCredential -> Bool
$c== :: ResetServiceSpecificCredential
-> ResetServiceSpecificCredential -> Bool
Prelude.Eq, ReadPrec [ResetServiceSpecificCredential]
ReadPrec ResetServiceSpecificCredential
Int -> ReadS ResetServiceSpecificCredential
ReadS [ResetServiceSpecificCredential]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResetServiceSpecificCredential]
$creadListPrec :: ReadPrec [ResetServiceSpecificCredential]
readPrec :: ReadPrec ResetServiceSpecificCredential
$creadPrec :: ReadPrec ResetServiceSpecificCredential
readList :: ReadS [ResetServiceSpecificCredential]
$creadList :: ReadS [ResetServiceSpecificCredential]
readsPrec :: Int -> ReadS ResetServiceSpecificCredential
$creadsPrec :: Int -> ReadS ResetServiceSpecificCredential
Prelude.Read, Int -> ResetServiceSpecificCredential -> ShowS
[ResetServiceSpecificCredential] -> ShowS
ResetServiceSpecificCredential -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetServiceSpecificCredential] -> ShowS
$cshowList :: [ResetServiceSpecificCredential] -> ShowS
show :: ResetServiceSpecificCredential -> String
$cshow :: ResetServiceSpecificCredential -> String
showsPrec :: Int -> ResetServiceSpecificCredential -> ShowS
$cshowsPrec :: Int -> ResetServiceSpecificCredential -> ShowS
Prelude.Show, forall x.
Rep ResetServiceSpecificCredential x
-> ResetServiceSpecificCredential
forall x.
ResetServiceSpecificCredential
-> Rep ResetServiceSpecificCredential x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ResetServiceSpecificCredential x
-> ResetServiceSpecificCredential
$cfrom :: forall x.
ResetServiceSpecificCredential
-> Rep ResetServiceSpecificCredential x
Prelude.Generic)

-- |
-- Create a value of 'ResetServiceSpecificCredential' 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:
--
-- 'userName', 'resetServiceSpecificCredential_userName' - The name of the IAM user associated with the service-specific
-- credential. If this value is not specified, then the operation assumes
-- the user whose credentials are used to call the operation.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
--
-- 'serviceSpecificCredentialId', 'resetServiceSpecificCredential_serviceSpecificCredentialId' - The unique identifier of the service-specific credential.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- that can consist of any upper or lowercased letter or digit.
newResetServiceSpecificCredential ::
  -- | 'serviceSpecificCredentialId'
  Prelude.Text ->
  ResetServiceSpecificCredential
newResetServiceSpecificCredential :: Text -> ResetServiceSpecificCredential
newResetServiceSpecificCredential
  Text
pServiceSpecificCredentialId_ =
    ResetServiceSpecificCredential'
      { $sel:userName:ResetServiceSpecificCredential' :: Maybe Text
userName =
          forall a. Maybe a
Prelude.Nothing,
        $sel:serviceSpecificCredentialId:ResetServiceSpecificCredential' :: Text
serviceSpecificCredentialId =
          Text
pServiceSpecificCredentialId_
      }

-- | The name of the IAM user associated with the service-specific
-- credential. If this value is not specified, then the operation assumes
-- the user whose credentials are used to call the operation.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
resetServiceSpecificCredential_userName :: Lens.Lens' ResetServiceSpecificCredential (Prelude.Maybe Prelude.Text)
resetServiceSpecificCredential_userName :: Lens' ResetServiceSpecificCredential (Maybe Text)
resetServiceSpecificCredential_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetServiceSpecificCredential' {Maybe Text
userName :: Maybe Text
$sel:userName:ResetServiceSpecificCredential' :: ResetServiceSpecificCredential -> Maybe Text
userName} -> Maybe Text
userName) (\s :: ResetServiceSpecificCredential
s@ResetServiceSpecificCredential' {} Maybe Text
a -> ResetServiceSpecificCredential
s {$sel:userName:ResetServiceSpecificCredential' :: Maybe Text
userName = Maybe Text
a} :: ResetServiceSpecificCredential)

-- | The unique identifier of the service-specific credential.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- that can consist of any upper or lowercased letter or digit.
resetServiceSpecificCredential_serviceSpecificCredentialId :: Lens.Lens' ResetServiceSpecificCredential Prelude.Text
resetServiceSpecificCredential_serviceSpecificCredentialId :: Lens' ResetServiceSpecificCredential Text
resetServiceSpecificCredential_serviceSpecificCredentialId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetServiceSpecificCredential' {Text
serviceSpecificCredentialId :: Text
$sel:serviceSpecificCredentialId:ResetServiceSpecificCredential' :: ResetServiceSpecificCredential -> Text
serviceSpecificCredentialId} -> Text
serviceSpecificCredentialId) (\s :: ResetServiceSpecificCredential
s@ResetServiceSpecificCredential' {} Text
a -> ResetServiceSpecificCredential
s {$sel:serviceSpecificCredentialId:ResetServiceSpecificCredential' :: Text
serviceSpecificCredentialId = Text
a} :: ResetServiceSpecificCredential)

instance
  Core.AWSRequest
    ResetServiceSpecificCredential
  where
  type
    AWSResponse ResetServiceSpecificCredential =
      ResetServiceSpecificCredentialResponse
  request :: (Service -> Service)
-> ResetServiceSpecificCredential
-> Request ResetServiceSpecificCredential
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ResetServiceSpecificCredential
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse ResetServiceSpecificCredential)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"ResetServiceSpecificCredentialResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe ServiceSpecificCredential
-> Int -> ResetServiceSpecificCredentialResponse
ResetServiceSpecificCredentialResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ServiceSpecificCredential")
            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
    ResetServiceSpecificCredential
  where
  hashWithSalt :: Int -> ResetServiceSpecificCredential -> Int
hashWithSalt
    Int
_salt
    ResetServiceSpecificCredential' {Maybe Text
Text
serviceSpecificCredentialId :: Text
userName :: Maybe Text
$sel:serviceSpecificCredentialId:ResetServiceSpecificCredential' :: ResetServiceSpecificCredential -> Text
$sel:userName:ResetServiceSpecificCredential' :: ResetServiceSpecificCredential -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
userName
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serviceSpecificCredentialId

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

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

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

instance Data.ToQuery ResetServiceSpecificCredential where
  toQuery :: ResetServiceSpecificCredential -> QueryString
toQuery ResetServiceSpecificCredential' {Maybe Text
Text
serviceSpecificCredentialId :: Text
userName :: Maybe Text
$sel:serviceSpecificCredentialId:ResetServiceSpecificCredential' :: ResetServiceSpecificCredential -> Text
$sel:userName:ResetServiceSpecificCredential' :: ResetServiceSpecificCredential -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"ResetServiceSpecificCredential" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString),
        ByteString
"UserName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
userName,
        ByteString
"ServiceSpecificCredentialId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
serviceSpecificCredentialId
      ]

-- | /See:/ 'newResetServiceSpecificCredentialResponse' smart constructor.
data ResetServiceSpecificCredentialResponse = ResetServiceSpecificCredentialResponse'
  { -- | A structure with details about the updated service-specific credential,
    -- including the new password.
    --
    -- This is the __only__ time that you can access the password. You cannot
    -- recover the password later, but you can reset it again.
    ResetServiceSpecificCredentialResponse
-> Maybe ServiceSpecificCredential
serviceSpecificCredential :: Prelude.Maybe ServiceSpecificCredential,
    -- | The response's http status code.
    ResetServiceSpecificCredentialResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ResetServiceSpecificCredentialResponse
-> ResetServiceSpecificCredentialResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetServiceSpecificCredentialResponse
-> ResetServiceSpecificCredentialResponse -> Bool
$c/= :: ResetServiceSpecificCredentialResponse
-> ResetServiceSpecificCredentialResponse -> Bool
== :: ResetServiceSpecificCredentialResponse
-> ResetServiceSpecificCredentialResponse -> Bool
$c== :: ResetServiceSpecificCredentialResponse
-> ResetServiceSpecificCredentialResponse -> Bool
Prelude.Eq, Int -> ResetServiceSpecificCredentialResponse -> ShowS
[ResetServiceSpecificCredentialResponse] -> ShowS
ResetServiceSpecificCredentialResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetServiceSpecificCredentialResponse] -> ShowS
$cshowList :: [ResetServiceSpecificCredentialResponse] -> ShowS
show :: ResetServiceSpecificCredentialResponse -> String
$cshow :: ResetServiceSpecificCredentialResponse -> String
showsPrec :: Int -> ResetServiceSpecificCredentialResponse -> ShowS
$cshowsPrec :: Int -> ResetServiceSpecificCredentialResponse -> ShowS
Prelude.Show, forall x.
Rep ResetServiceSpecificCredentialResponse x
-> ResetServiceSpecificCredentialResponse
forall x.
ResetServiceSpecificCredentialResponse
-> Rep ResetServiceSpecificCredentialResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ResetServiceSpecificCredentialResponse x
-> ResetServiceSpecificCredentialResponse
$cfrom :: forall x.
ResetServiceSpecificCredentialResponse
-> Rep ResetServiceSpecificCredentialResponse x
Prelude.Generic)

-- |
-- Create a value of 'ResetServiceSpecificCredentialResponse' 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:
--
-- 'serviceSpecificCredential', 'resetServiceSpecificCredentialResponse_serviceSpecificCredential' - A structure with details about the updated service-specific credential,
-- including the new password.
--
-- This is the __only__ time that you can access the password. You cannot
-- recover the password later, but you can reset it again.
--
-- 'httpStatus', 'resetServiceSpecificCredentialResponse_httpStatus' - The response's http status code.
newResetServiceSpecificCredentialResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ResetServiceSpecificCredentialResponse
newResetServiceSpecificCredentialResponse :: Int -> ResetServiceSpecificCredentialResponse
newResetServiceSpecificCredentialResponse
  Int
pHttpStatus_ =
    ResetServiceSpecificCredentialResponse'
      { $sel:serviceSpecificCredential:ResetServiceSpecificCredentialResponse' :: Maybe ServiceSpecificCredential
serviceSpecificCredential =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ResetServiceSpecificCredentialResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | A structure with details about the updated service-specific credential,
-- including the new password.
--
-- This is the __only__ time that you can access the password. You cannot
-- recover the password later, but you can reset it again.
resetServiceSpecificCredentialResponse_serviceSpecificCredential :: Lens.Lens' ResetServiceSpecificCredentialResponse (Prelude.Maybe ServiceSpecificCredential)
resetServiceSpecificCredentialResponse_serviceSpecificCredential :: Lens'
  ResetServiceSpecificCredentialResponse
  (Maybe ServiceSpecificCredential)
resetServiceSpecificCredentialResponse_serviceSpecificCredential = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetServiceSpecificCredentialResponse' {Maybe ServiceSpecificCredential
serviceSpecificCredential :: Maybe ServiceSpecificCredential
$sel:serviceSpecificCredential:ResetServiceSpecificCredentialResponse' :: ResetServiceSpecificCredentialResponse
-> Maybe ServiceSpecificCredential
serviceSpecificCredential} -> Maybe ServiceSpecificCredential
serviceSpecificCredential) (\s :: ResetServiceSpecificCredentialResponse
s@ResetServiceSpecificCredentialResponse' {} Maybe ServiceSpecificCredential
a -> ResetServiceSpecificCredentialResponse
s {$sel:serviceSpecificCredential:ResetServiceSpecificCredentialResponse' :: Maybe ServiceSpecificCredential
serviceSpecificCredential = Maybe ServiceSpecificCredential
a} :: ResetServiceSpecificCredentialResponse)

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

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