{-# 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.EnableMFADevice
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Enables the specified MFA device and associates it with the specified
-- IAM user. When enabled, the MFA device is required for every subsequent
-- login by the IAM user associated with the device.
module Amazonka.IAM.EnableMFADevice
  ( -- * Creating a Request
    EnableMFADevice (..),
    newEnableMFADevice,

    -- * Request Lenses
    enableMFADevice_userName,
    enableMFADevice_serialNumber,
    enableMFADevice_authenticationCode1,
    enableMFADevice_authenticationCode2,

    -- * Destructuring the Response
    EnableMFADeviceResponse (..),
    newEnableMFADeviceResponse,
  )
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:/ 'newEnableMFADevice' smart constructor.
data EnableMFADevice = EnableMFADevice'
  { -- | The name of the IAM user for whom you want to enable 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: _+=,.\@-
    EnableMFADevice -> Text
userName :: Prelude.Text,
    -- | The serial number that uniquely identifies the MFA device. For virtual
    -- MFA devices, the serial number is the device ARN.
    --
    -- 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: =,.\@:\/-
    EnableMFADevice -> Text
serialNumber :: Prelude.Text,
    -- | An authentication code emitted by the device.
    --
    -- The format for this parameter is a string of six digits.
    --
    -- Submit your request immediately after generating the authentication
    -- codes. If you generate the codes and then wait too long to submit the
    -- request, the MFA device successfully associates with the user but the
    -- MFA device becomes out of sync. This happens because time-based one-time
    -- passwords (TOTP) expire after a short period of time. If this happens,
    -- you can
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_credentials_mfa_sync.html resync the device>.
    EnableMFADevice -> Text
authenticationCode1 :: Prelude.Text,
    -- | A subsequent authentication code emitted by the device.
    --
    -- The format for this parameter is a string of six digits.
    --
    -- Submit your request immediately after generating the authentication
    -- codes. If you generate the codes and then wait too long to submit the
    -- request, the MFA device successfully associates with the user but the
    -- MFA device becomes out of sync. This happens because time-based one-time
    -- passwords (TOTP) expire after a short period of time. If this happens,
    -- you can
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_credentials_mfa_sync.html resync the device>.
    EnableMFADevice -> Text
authenticationCode2 :: Prelude.Text
  }
  deriving (EnableMFADevice -> EnableMFADevice -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableMFADevice -> EnableMFADevice -> Bool
$c/= :: EnableMFADevice -> EnableMFADevice -> Bool
== :: EnableMFADevice -> EnableMFADevice -> Bool
$c== :: EnableMFADevice -> EnableMFADevice -> Bool
Prelude.Eq, ReadPrec [EnableMFADevice]
ReadPrec EnableMFADevice
Int -> ReadS EnableMFADevice
ReadS [EnableMFADevice]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableMFADevice]
$creadListPrec :: ReadPrec [EnableMFADevice]
readPrec :: ReadPrec EnableMFADevice
$creadPrec :: ReadPrec EnableMFADevice
readList :: ReadS [EnableMFADevice]
$creadList :: ReadS [EnableMFADevice]
readsPrec :: Int -> ReadS EnableMFADevice
$creadsPrec :: Int -> ReadS EnableMFADevice
Prelude.Read, Int -> EnableMFADevice -> ShowS
[EnableMFADevice] -> ShowS
EnableMFADevice -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableMFADevice] -> ShowS
$cshowList :: [EnableMFADevice] -> ShowS
show :: EnableMFADevice -> String
$cshow :: EnableMFADevice -> String
showsPrec :: Int -> EnableMFADevice -> ShowS
$cshowsPrec :: Int -> EnableMFADevice -> ShowS
Prelude.Show, forall x. Rep EnableMFADevice x -> EnableMFADevice
forall x. EnableMFADevice -> Rep EnableMFADevice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableMFADevice x -> EnableMFADevice
$cfrom :: forall x. EnableMFADevice -> Rep EnableMFADevice x
Prelude.Generic)

-- |
-- Create a value of 'EnableMFADevice' 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', 'enableMFADevice_userName' - The name of the IAM user for whom you want to enable 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: _+=,.\@-
--
-- 'serialNumber', 'enableMFADevice_serialNumber' - The serial number that uniquely identifies the MFA device. For virtual
-- MFA devices, the serial number is the device ARN.
--
-- 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', 'enableMFADevice_authenticationCode1' - An authentication code emitted by the device.
--
-- The format for this parameter is a string of six digits.
--
-- Submit your request immediately after generating the authentication
-- codes. If you generate the codes and then wait too long to submit the
-- request, the MFA device successfully associates with the user but the
-- MFA device becomes out of sync. This happens because time-based one-time
-- passwords (TOTP) expire after a short period of time. If this happens,
-- you can
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_credentials_mfa_sync.html resync the device>.
--
-- 'authenticationCode2', 'enableMFADevice_authenticationCode2' - A subsequent authentication code emitted by the device.
--
-- The format for this parameter is a string of six digits.
--
-- Submit your request immediately after generating the authentication
-- codes. If you generate the codes and then wait too long to submit the
-- request, the MFA device successfully associates with the user but the
-- MFA device becomes out of sync. This happens because time-based one-time
-- passwords (TOTP) expire after a short period of time. If this happens,
-- you can
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_credentials_mfa_sync.html resync the device>.
newEnableMFADevice ::
  -- | 'userName'
  Prelude.Text ->
  -- | 'serialNumber'
  Prelude.Text ->
  -- | 'authenticationCode1'
  Prelude.Text ->
  -- | 'authenticationCode2'
  Prelude.Text ->
  EnableMFADevice
newEnableMFADevice :: Text -> Text -> Text -> Text -> EnableMFADevice
newEnableMFADevice
  Text
pUserName_
  Text
pSerialNumber_
  Text
pAuthenticationCode1_
  Text
pAuthenticationCode2_ =
    EnableMFADevice'
      { $sel:userName:EnableMFADevice' :: Text
userName = Text
pUserName_,
        $sel:serialNumber:EnableMFADevice' :: Text
serialNumber = Text
pSerialNumber_,
        $sel:authenticationCode1:EnableMFADevice' :: Text
authenticationCode1 = Text
pAuthenticationCode1_,
        $sel:authenticationCode2:EnableMFADevice' :: Text
authenticationCode2 = Text
pAuthenticationCode2_
      }

-- | The name of the IAM user for whom you want to enable 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: _+=,.\@-
enableMFADevice_userName :: Lens.Lens' EnableMFADevice Prelude.Text
enableMFADevice_userName :: Lens' EnableMFADevice Text
enableMFADevice_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableMFADevice' {Text
userName :: Text
$sel:userName:EnableMFADevice' :: EnableMFADevice -> Text
userName} -> Text
userName) (\s :: EnableMFADevice
s@EnableMFADevice' {} Text
a -> EnableMFADevice
s {$sel:userName:EnableMFADevice' :: Text
userName = Text
a} :: EnableMFADevice)

-- | The serial number that uniquely identifies the MFA device. For virtual
-- MFA devices, the serial number is the device ARN.
--
-- 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: =,.\@:\/-
enableMFADevice_serialNumber :: Lens.Lens' EnableMFADevice Prelude.Text
enableMFADevice_serialNumber :: Lens' EnableMFADevice Text
enableMFADevice_serialNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableMFADevice' {Text
serialNumber :: Text
$sel:serialNumber:EnableMFADevice' :: EnableMFADevice -> Text
serialNumber} -> Text
serialNumber) (\s :: EnableMFADevice
s@EnableMFADevice' {} Text
a -> EnableMFADevice
s {$sel:serialNumber:EnableMFADevice' :: Text
serialNumber = Text
a} :: EnableMFADevice)

-- | An authentication code emitted by the device.
--
-- The format for this parameter is a string of six digits.
--
-- Submit your request immediately after generating the authentication
-- codes. If you generate the codes and then wait too long to submit the
-- request, the MFA device successfully associates with the user but the
-- MFA device becomes out of sync. This happens because time-based one-time
-- passwords (TOTP) expire after a short period of time. If this happens,
-- you can
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_credentials_mfa_sync.html resync the device>.
enableMFADevice_authenticationCode1 :: Lens.Lens' EnableMFADevice Prelude.Text
enableMFADevice_authenticationCode1 :: Lens' EnableMFADevice Text
enableMFADevice_authenticationCode1 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableMFADevice' {Text
authenticationCode1 :: Text
$sel:authenticationCode1:EnableMFADevice' :: EnableMFADevice -> Text
authenticationCode1} -> Text
authenticationCode1) (\s :: EnableMFADevice
s@EnableMFADevice' {} Text
a -> EnableMFADevice
s {$sel:authenticationCode1:EnableMFADevice' :: Text
authenticationCode1 = Text
a} :: EnableMFADevice)

-- | A subsequent authentication code emitted by the device.
--
-- The format for this parameter is a string of six digits.
--
-- Submit your request immediately after generating the authentication
-- codes. If you generate the codes and then wait too long to submit the
-- request, the MFA device successfully associates with the user but the
-- MFA device becomes out of sync. This happens because time-based one-time
-- passwords (TOTP) expire after a short period of time. If this happens,
-- you can
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_credentials_mfa_sync.html resync the device>.
enableMFADevice_authenticationCode2 :: Lens.Lens' EnableMFADevice Prelude.Text
enableMFADevice_authenticationCode2 :: Lens' EnableMFADevice Text
enableMFADevice_authenticationCode2 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableMFADevice' {Text
authenticationCode2 :: Text
$sel:authenticationCode2:EnableMFADevice' :: EnableMFADevice -> Text
authenticationCode2} -> Text
authenticationCode2) (\s :: EnableMFADevice
s@EnableMFADevice' {} Text
a -> EnableMFADevice
s {$sel:authenticationCode2:EnableMFADevice' :: Text
authenticationCode2 = Text
a} :: EnableMFADevice)

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

instance Prelude.Hashable EnableMFADevice where
  hashWithSalt :: Int -> EnableMFADevice -> Int
hashWithSalt Int
_salt EnableMFADevice' {Text
authenticationCode2 :: Text
authenticationCode1 :: Text
serialNumber :: Text
userName :: Text
$sel:authenticationCode2:EnableMFADevice' :: EnableMFADevice -> Text
$sel:authenticationCode1:EnableMFADevice' :: EnableMFADevice -> Text
$sel:serialNumber:EnableMFADevice' :: EnableMFADevice -> Text
$sel:userName:EnableMFADevice' :: EnableMFADevice -> 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 EnableMFADevice where
  rnf :: EnableMFADevice -> ()
rnf EnableMFADevice' {Text
authenticationCode2 :: Text
authenticationCode1 :: Text
serialNumber :: Text
userName :: Text
$sel:authenticationCode2:EnableMFADevice' :: EnableMFADevice -> Text
$sel:authenticationCode1:EnableMFADevice' :: EnableMFADevice -> Text
$sel:serialNumber:EnableMFADevice' :: EnableMFADevice -> Text
$sel:userName:EnableMFADevice' :: EnableMFADevice -> 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 EnableMFADevice where
  toHeaders :: EnableMFADevice -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery EnableMFADevice where
  toQuery :: EnableMFADevice -> QueryString
toQuery EnableMFADevice' {Text
authenticationCode2 :: Text
authenticationCode1 :: Text
serialNumber :: Text
userName :: Text
$sel:authenticationCode2:EnableMFADevice' :: EnableMFADevice -> Text
$sel:authenticationCode1:EnableMFADevice' :: EnableMFADevice -> Text
$sel:serialNumber:EnableMFADevice' :: EnableMFADevice -> Text
$sel:userName:EnableMFADevice' :: EnableMFADevice -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"EnableMFADevice" :: 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:/ 'newEnableMFADeviceResponse' smart constructor.
data EnableMFADeviceResponse = EnableMFADeviceResponse'
  {
  }
  deriving (EnableMFADeviceResponse -> EnableMFADeviceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableMFADeviceResponse -> EnableMFADeviceResponse -> Bool
$c/= :: EnableMFADeviceResponse -> EnableMFADeviceResponse -> Bool
== :: EnableMFADeviceResponse -> EnableMFADeviceResponse -> Bool
$c== :: EnableMFADeviceResponse -> EnableMFADeviceResponse -> Bool
Prelude.Eq, ReadPrec [EnableMFADeviceResponse]
ReadPrec EnableMFADeviceResponse
Int -> ReadS EnableMFADeviceResponse
ReadS [EnableMFADeviceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableMFADeviceResponse]
$creadListPrec :: ReadPrec [EnableMFADeviceResponse]
readPrec :: ReadPrec EnableMFADeviceResponse
$creadPrec :: ReadPrec EnableMFADeviceResponse
readList :: ReadS [EnableMFADeviceResponse]
$creadList :: ReadS [EnableMFADeviceResponse]
readsPrec :: Int -> ReadS EnableMFADeviceResponse
$creadsPrec :: Int -> ReadS EnableMFADeviceResponse
Prelude.Read, Int -> EnableMFADeviceResponse -> ShowS
[EnableMFADeviceResponse] -> ShowS
EnableMFADeviceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableMFADeviceResponse] -> ShowS
$cshowList :: [EnableMFADeviceResponse] -> ShowS
show :: EnableMFADeviceResponse -> String
$cshow :: EnableMFADeviceResponse -> String
showsPrec :: Int -> EnableMFADeviceResponse -> ShowS
$cshowsPrec :: Int -> EnableMFADeviceResponse -> ShowS
Prelude.Show, forall x. Rep EnableMFADeviceResponse x -> EnableMFADeviceResponse
forall x. EnableMFADeviceResponse -> Rep EnableMFADeviceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableMFADeviceResponse x -> EnableMFADeviceResponse
$cfrom :: forall x. EnableMFADeviceResponse -> Rep EnableMFADeviceResponse x
Prelude.Generic)

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

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