{-# 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.GetLoginProfile
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the user name for the specified IAM user. A login profile is
-- created when you create a password for the user to access the Amazon Web
-- Services Management Console. If the user does not exist or does not have
-- a password, the operation returns a 404 (@NoSuchEntity@) error.
--
-- If you create an IAM user with access to the console, the @CreateDate@
-- reflects the date you created the initial password for the user.
--
-- If you create an IAM user with programmatic access, and then later add a
-- password for the user to access the Amazon Web Services Management
-- Console, the @CreateDate@ reflects the initial password creation date. A
-- user with programmatic access does not have a login profile unless you
-- create a password for the user to access the Amazon Web Services
-- Management Console.
module Amazonka.IAM.GetLoginProfile
  ( -- * Creating a Request
    GetLoginProfile (..),
    newGetLoginProfile,

    -- * Request Lenses
    getLoginProfile_userName,

    -- * Destructuring the Response
    GetLoginProfileResponse (..),
    newGetLoginProfileResponse,

    -- * Response Lenses
    getLoginProfileResponse_httpStatus,
    getLoginProfileResponse_loginProfile,
  )
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:/ 'newGetLoginProfile' smart constructor.
data GetLoginProfile = GetLoginProfile'
  { -- | The name of the user whose login profile you want to retrieve.
    --
    -- 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: _+=,.\@-
    GetLoginProfile -> Text
userName :: Prelude.Text
  }
  deriving (GetLoginProfile -> GetLoginProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLoginProfile -> GetLoginProfile -> Bool
$c/= :: GetLoginProfile -> GetLoginProfile -> Bool
== :: GetLoginProfile -> GetLoginProfile -> Bool
$c== :: GetLoginProfile -> GetLoginProfile -> Bool
Prelude.Eq, ReadPrec [GetLoginProfile]
ReadPrec GetLoginProfile
Int -> ReadS GetLoginProfile
ReadS [GetLoginProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetLoginProfile]
$creadListPrec :: ReadPrec [GetLoginProfile]
readPrec :: ReadPrec GetLoginProfile
$creadPrec :: ReadPrec GetLoginProfile
readList :: ReadS [GetLoginProfile]
$creadList :: ReadS [GetLoginProfile]
readsPrec :: Int -> ReadS GetLoginProfile
$creadsPrec :: Int -> ReadS GetLoginProfile
Prelude.Read, Int -> GetLoginProfile -> ShowS
[GetLoginProfile] -> ShowS
GetLoginProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLoginProfile] -> ShowS
$cshowList :: [GetLoginProfile] -> ShowS
show :: GetLoginProfile -> String
$cshow :: GetLoginProfile -> String
showsPrec :: Int -> GetLoginProfile -> ShowS
$cshowsPrec :: Int -> GetLoginProfile -> ShowS
Prelude.Show, forall x. Rep GetLoginProfile x -> GetLoginProfile
forall x. GetLoginProfile -> Rep GetLoginProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLoginProfile x -> GetLoginProfile
$cfrom :: forall x. GetLoginProfile -> Rep GetLoginProfile x
Prelude.Generic)

-- |
-- Create a value of 'GetLoginProfile' 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', 'getLoginProfile_userName' - The name of the user whose login profile you want to retrieve.
--
-- 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: _+=,.\@-
newGetLoginProfile ::
  -- | 'userName'
  Prelude.Text ->
  GetLoginProfile
newGetLoginProfile :: Text -> GetLoginProfile
newGetLoginProfile Text
pUserName_ =
  GetLoginProfile' {$sel:userName:GetLoginProfile' :: Text
userName = Text
pUserName_}

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

instance Core.AWSRequest GetLoginProfile where
  type
    AWSResponse GetLoginProfile =
      GetLoginProfileResponse
  request :: (Service -> Service) -> GetLoginProfile -> Request GetLoginProfile
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 GetLoginProfile
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetLoginProfile)))
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
"GetLoginProfileResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> LoginProfile -> GetLoginProfileResponse
GetLoginProfileResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"LoginProfile")
      )

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

instance Prelude.NFData GetLoginProfile where
  rnf :: GetLoginProfile -> ()
rnf GetLoginProfile' {Text
userName :: Text
$sel:userName:GetLoginProfile' :: GetLoginProfile -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
userName

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

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

instance Data.ToQuery GetLoginProfile where
  toQuery :: GetLoginProfile -> QueryString
toQuery GetLoginProfile' {Text
userName :: Text
$sel:userName:GetLoginProfile' :: GetLoginProfile -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetLoginProfile" :: 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
      ]

-- | Contains the response to a successful GetLoginProfile request.
--
-- /See:/ 'newGetLoginProfileResponse' smart constructor.
data GetLoginProfileResponse = GetLoginProfileResponse'
  { -- | The response's http status code.
    GetLoginProfileResponse -> Int
httpStatus :: Prelude.Int,
    -- | A structure containing the user name and the profile creation date for
    -- the user.
    GetLoginProfileResponse -> LoginProfile
loginProfile :: LoginProfile
  }
  deriving (GetLoginProfileResponse -> GetLoginProfileResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLoginProfileResponse -> GetLoginProfileResponse -> Bool
$c/= :: GetLoginProfileResponse -> GetLoginProfileResponse -> Bool
== :: GetLoginProfileResponse -> GetLoginProfileResponse -> Bool
$c== :: GetLoginProfileResponse -> GetLoginProfileResponse -> Bool
Prelude.Eq, ReadPrec [GetLoginProfileResponse]
ReadPrec GetLoginProfileResponse
Int -> ReadS GetLoginProfileResponse
ReadS [GetLoginProfileResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetLoginProfileResponse]
$creadListPrec :: ReadPrec [GetLoginProfileResponse]
readPrec :: ReadPrec GetLoginProfileResponse
$creadPrec :: ReadPrec GetLoginProfileResponse
readList :: ReadS [GetLoginProfileResponse]
$creadList :: ReadS [GetLoginProfileResponse]
readsPrec :: Int -> ReadS GetLoginProfileResponse
$creadsPrec :: Int -> ReadS GetLoginProfileResponse
Prelude.Read, Int -> GetLoginProfileResponse -> ShowS
[GetLoginProfileResponse] -> ShowS
GetLoginProfileResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLoginProfileResponse] -> ShowS
$cshowList :: [GetLoginProfileResponse] -> ShowS
show :: GetLoginProfileResponse -> String
$cshow :: GetLoginProfileResponse -> String
showsPrec :: Int -> GetLoginProfileResponse -> ShowS
$cshowsPrec :: Int -> GetLoginProfileResponse -> ShowS
Prelude.Show, forall x. Rep GetLoginProfileResponse x -> GetLoginProfileResponse
forall x. GetLoginProfileResponse -> Rep GetLoginProfileResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLoginProfileResponse x -> GetLoginProfileResponse
$cfrom :: forall x. GetLoginProfileResponse -> Rep GetLoginProfileResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetLoginProfileResponse' 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:
--
-- 'httpStatus', 'getLoginProfileResponse_httpStatus' - The response's http status code.
--
-- 'loginProfile', 'getLoginProfileResponse_loginProfile' - A structure containing the user name and the profile creation date for
-- the user.
newGetLoginProfileResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'loginProfile'
  LoginProfile ->
  GetLoginProfileResponse
newGetLoginProfileResponse :: Int -> LoginProfile -> GetLoginProfileResponse
newGetLoginProfileResponse
  Int
pHttpStatus_
  LoginProfile
pLoginProfile_ =
    GetLoginProfileResponse'
      { $sel:httpStatus:GetLoginProfileResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:loginProfile:GetLoginProfileResponse' :: LoginProfile
loginProfile = LoginProfile
pLoginProfile_
      }

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

-- | A structure containing the user name and the profile creation date for
-- the user.
getLoginProfileResponse_loginProfile :: Lens.Lens' GetLoginProfileResponse LoginProfile
getLoginProfileResponse_loginProfile :: Lens' GetLoginProfileResponse LoginProfile
getLoginProfileResponse_loginProfile = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLoginProfileResponse' {LoginProfile
loginProfile :: LoginProfile
$sel:loginProfile:GetLoginProfileResponse' :: GetLoginProfileResponse -> LoginProfile
loginProfile} -> LoginProfile
loginProfile) (\s :: GetLoginProfileResponse
s@GetLoginProfileResponse' {} LoginProfile
a -> GetLoginProfileResponse
s {$sel:loginProfile:GetLoginProfileResponse' :: LoginProfile
loginProfile = LoginProfile
a} :: GetLoginProfileResponse)

instance Prelude.NFData GetLoginProfileResponse where
  rnf :: GetLoginProfileResponse -> ()
rnf GetLoginProfileResponse' {Int
LoginProfile
loginProfile :: LoginProfile
httpStatus :: Int
$sel:loginProfile:GetLoginProfileResponse' :: GetLoginProfileResponse -> LoginProfile
$sel:httpStatus:GetLoginProfileResponse' :: GetLoginProfileResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf LoginProfile
loginProfile