{-# 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.ResyncMFADevice
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Synchronizes the specified MFA device with its IAM resource object on
-- the Amazon Web Services servers.
--
-- For more information about creating and working with virtual MFA
-- devices, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/Using_VirtualMFA.html Using a virtual MFA device>
-- in the /IAM User Guide/.
module Amazonka.IAM.ResyncMFADevice
  ( -- * Creating a Request
    ResyncMFADevice (..),
    newResyncMFADevice,

    -- * Request Lenses
    resyncMFADevice_userName,
    resyncMFADevice_serialNumber,
    resyncMFADevice_authenticationCode1,
    resyncMFADevice_authenticationCode2,

    -- * Destructuring the Response
    ResyncMFADeviceResponse (..),
    newResyncMFADeviceResponse,
  )
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:/ 'newResyncMFADevice' smart constructor.
data ResyncMFADevice = ResyncMFADevice'
  { -- | The name of the user whose MFA device you want to resynchronize.
    --
    -- 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: _+=,.\@-
    ResyncMFADevice -> Text
userName :: Prelude.Text,
    -- | Serial number that uniquely identifies the MFA device.
    --
    -- 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: _+=,.\@-
    ResyncMFADevice -> Text
serialNumber :: Prelude.Text,
    -- | An authentication code emitted by the device.
    --
    -- The format for this parameter is a sequence of six digits.
    ResyncMFADevice -> Text
authenticationCode1 :: Prelude.Text,
    -- | A subsequent authentication code emitted by the device.
    --
    -- The format for this parameter is a sequence of six digits.
    ResyncMFADevice -> Text
authenticationCode2 :: Prelude.Text
  }
  deriving (ResyncMFADevice -> ResyncMFADevice -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResyncMFADevice -> ResyncMFADevice -> Bool
$c/= :: ResyncMFADevice -> ResyncMFADevice -> Bool
== :: ResyncMFADevice -> ResyncMFADevice -> Bool
$c== :: ResyncMFADevice -> ResyncMFADevice -> Bool
Prelude.Eq, ReadPrec [ResyncMFADevice]
ReadPrec ResyncMFADevice
Int -> ReadS ResyncMFADevice
ReadS [ResyncMFADevice]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResyncMFADevice]
$creadListPrec :: ReadPrec [ResyncMFADevice]
readPrec :: ReadPrec ResyncMFADevice
$creadPrec :: ReadPrec ResyncMFADevice
readList :: ReadS [ResyncMFADevice]
$creadList :: ReadS [ResyncMFADevice]
readsPrec :: Int -> ReadS ResyncMFADevice
$creadsPrec :: Int -> ReadS ResyncMFADevice
Prelude.Read, Int -> ResyncMFADevice -> ShowS
[ResyncMFADevice] -> ShowS
ResyncMFADevice -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResyncMFADevice] -> ShowS
$cshowList :: [ResyncMFADevice] -> ShowS
show :: ResyncMFADevice -> String
$cshow :: ResyncMFADevice -> String
showsPrec :: Int -> ResyncMFADevice -> ShowS
$cshowsPrec :: Int -> ResyncMFADevice -> ShowS
Prelude.Show, forall x. Rep ResyncMFADevice x -> ResyncMFADevice
forall x. ResyncMFADevice -> Rep ResyncMFADevice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResyncMFADevice x -> ResyncMFADevice
$cfrom :: forall x. ResyncMFADevice -> Rep ResyncMFADevice x
Prelude.Generic)

-- |
-- Create a value of 'ResyncMFADevice' 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', 'resyncMFADevice_userName' - The name of the user whose MFA device you want to resynchronize.
--
-- 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: _+=,.\@-
--
-- 'serialNumber', 'resyncMFADevice_serialNumber' - Serial number that uniquely identifies the MFA device.
--
-- 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: _+=,.\@-
--
-- 'authenticationCode1', 'resyncMFADevice_authenticationCode1' - An authentication code emitted by the device.
--
-- The format for this parameter is a sequence of six digits.
--
-- 'authenticationCode2', 'resyncMFADevice_authenticationCode2' - A subsequent authentication code emitted by the device.
--
-- The format for this parameter is a sequence of six digits.
newResyncMFADevice ::
  -- | 'userName'
  Prelude.Text ->
  -- | 'serialNumber'
  Prelude.Text ->
  -- | 'authenticationCode1'
  Prelude.Text ->
  -- | 'authenticationCode2'
  Prelude.Text ->
  ResyncMFADevice
newResyncMFADevice :: Text -> Text -> Text -> Text -> ResyncMFADevice
newResyncMFADevice
  Text
pUserName_
  Text
pSerialNumber_
  Text
pAuthenticationCode1_
  Text
pAuthenticationCode2_ =
    ResyncMFADevice'
      { $sel:userName:ResyncMFADevice' :: Text
userName = Text
pUserName_,
        $sel:serialNumber:ResyncMFADevice' :: Text
serialNumber = Text
pSerialNumber_,
        $sel:authenticationCode1:ResyncMFADevice' :: Text
authenticationCode1 = Text
pAuthenticationCode1_,
        $sel:authenticationCode2:ResyncMFADevice' :: Text
authenticationCode2 = Text
pAuthenticationCode2_
      }

-- | The name of the user whose MFA device you want to resynchronize.
--
-- 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: _+=,.\@-
resyncMFADevice_userName :: Lens.Lens' ResyncMFADevice Prelude.Text
resyncMFADevice_userName :: Lens' ResyncMFADevice Text
resyncMFADevice_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResyncMFADevice' {Text
userName :: Text
$sel:userName:ResyncMFADevice' :: ResyncMFADevice -> Text
userName} -> Text
userName) (\s :: ResyncMFADevice
s@ResyncMFADevice' {} Text
a -> ResyncMFADevice
s {$sel:userName:ResyncMFADevice' :: Text
userName = Text
a} :: ResyncMFADevice)

-- | Serial number that uniquely identifies the MFA device.
--
-- 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: _+=,.\@-
resyncMFADevice_serialNumber :: Lens.Lens' ResyncMFADevice Prelude.Text
resyncMFADevice_serialNumber :: Lens' ResyncMFADevice Text
resyncMFADevice_serialNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResyncMFADevice' {Text
serialNumber :: Text
$sel:serialNumber:ResyncMFADevice' :: ResyncMFADevice -> Text
serialNumber} -> Text
serialNumber) (\s :: ResyncMFADevice
s@ResyncMFADevice' {} Text
a -> ResyncMFADevice
s {$sel:serialNumber:ResyncMFADevice' :: Text
serialNumber = Text
a} :: ResyncMFADevice)

-- | An authentication code emitted by the device.
--
-- The format for this parameter is a sequence of six digits.
resyncMFADevice_authenticationCode1 :: Lens.Lens' ResyncMFADevice Prelude.Text
resyncMFADevice_authenticationCode1 :: Lens' ResyncMFADevice Text
resyncMFADevice_authenticationCode1 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResyncMFADevice' {Text
authenticationCode1 :: Text
$sel:authenticationCode1:ResyncMFADevice' :: ResyncMFADevice -> Text
authenticationCode1} -> Text
authenticationCode1) (\s :: ResyncMFADevice
s@ResyncMFADevice' {} Text
a -> ResyncMFADevice
s {$sel:authenticationCode1:ResyncMFADevice' :: Text
authenticationCode1 = Text
a} :: ResyncMFADevice)

-- | A subsequent authentication code emitted by the device.
--
-- The format for this parameter is a sequence of six digits.
resyncMFADevice_authenticationCode2 :: Lens.Lens' ResyncMFADevice Prelude.Text
resyncMFADevice_authenticationCode2 :: Lens' ResyncMFADevice Text
resyncMFADevice_authenticationCode2 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResyncMFADevice' {Text
authenticationCode2 :: Text
$sel:authenticationCode2:ResyncMFADevice' :: ResyncMFADevice -> Text
authenticationCode2} -> Text
authenticationCode2) (\s :: ResyncMFADevice
s@ResyncMFADevice' {} Text
a -> ResyncMFADevice
s {$sel:authenticationCode2:ResyncMFADevice' :: Text
authenticationCode2 = Text
a} :: ResyncMFADevice)

instance Core.AWSRequest ResyncMFADevice where
  type
    AWSResponse ResyncMFADevice =
      ResyncMFADeviceResponse
  request :: (Service -> Service) -> ResyncMFADevice -> Request ResyncMFADevice
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 ResyncMFADevice
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ResyncMFADevice)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull ResyncMFADeviceResponse
ResyncMFADeviceResponse'

instance Prelude.Hashable ResyncMFADevice where
  hashWithSalt :: Int -> ResyncMFADevice -> Int
hashWithSalt Int
_salt ResyncMFADevice' {Text
authenticationCode2 :: Text
authenticationCode1 :: Text
serialNumber :: Text
userName :: Text
$sel:authenticationCode2:ResyncMFADevice' :: ResyncMFADevice -> Text
$sel:authenticationCode1:ResyncMFADevice' :: ResyncMFADevice -> Text
$sel:serialNumber:ResyncMFADevice' :: ResyncMFADevice -> Text
$sel:userName:ResyncMFADevice' :: ResyncMFADevice -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serialNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
authenticationCode1
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
authenticationCode2

instance Prelude.NFData ResyncMFADevice where
  rnf :: ResyncMFADevice -> ()
rnf ResyncMFADevice' {Text
authenticationCode2 :: Text
authenticationCode1 :: Text
serialNumber :: Text
userName :: Text
$sel:authenticationCode2:ResyncMFADevice' :: ResyncMFADevice -> Text
$sel:authenticationCode1:ResyncMFADevice' :: ResyncMFADevice -> Text
$sel:serialNumber:ResyncMFADevice' :: ResyncMFADevice -> Text
$sel:userName:ResyncMFADevice' :: ResyncMFADevice -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
userName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serialNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
authenticationCode1
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
authenticationCode2

instance Data.ToHeaders ResyncMFADevice where
  toHeaders :: ResyncMFADevice -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery ResyncMFADevice where
  toQuery :: ResyncMFADevice -> QueryString
toQuery ResyncMFADevice' {Text
authenticationCode2 :: Text
authenticationCode1 :: Text
serialNumber :: Text
userName :: Text
$sel:authenticationCode2:ResyncMFADevice' :: ResyncMFADevice -> Text
$sel:authenticationCode1:ResyncMFADevice' :: ResyncMFADevice -> Text
$sel:serialNumber:ResyncMFADevice' :: ResyncMFADevice -> Text
$sel:userName:ResyncMFADevice' :: ResyncMFADevice -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ResyncMFADevice" :: 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.=: Text
userName,
        ByteString
"SerialNumber" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
serialNumber,
        ByteString
"AuthenticationCode1" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
authenticationCode1,
        ByteString
"AuthenticationCode2" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
authenticationCode2
      ]

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

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

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