{-# 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.CognitoIdentityProvider.AdminLinkProviderForUser
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Links an existing user account in a user pool (@DestinationUser@) to an
-- identity from an external IdP (@SourceUser@) based on a specified
-- attribute name and value from the external IdP. This allows you to
-- create a link from the existing user account to an external federated
-- user identity that has not yet been used to sign in. You can then use
-- the federated user identity to sign in as the existing user account.
--
-- For example, if there is an existing user with a username and password,
-- this API links that user to a federated user identity. When the user
-- signs in with a federated user identity, they sign in as the existing
-- user account.
--
-- The maximum number of federated identities linked to a user is five.
--
-- Because this API allows a user with an external federated identity to
-- sign in as an existing user in the user pool, it is critical that it
-- only be used with external IdPs and provider attributes that have been
-- trusted by the application owner.
--
-- This action is administrative and requires developer credentials.
module Amazonka.CognitoIdentityProvider.AdminLinkProviderForUser
  ( -- * Creating a Request
    AdminLinkProviderForUser (..),
    newAdminLinkProviderForUser,

    -- * Request Lenses
    adminLinkProviderForUser_userPoolId,
    adminLinkProviderForUser_destinationUser,
    adminLinkProviderForUser_sourceUser,

    -- * Destructuring the Response
    AdminLinkProviderForUserResponse (..),
    newAdminLinkProviderForUserResponse,

    -- * Response Lenses
    adminLinkProviderForUserResponse_httpStatus,
  )
where

import Amazonka.CognitoIdentityProvider.Types
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

-- | /See:/ 'newAdminLinkProviderForUser' smart constructor.
data AdminLinkProviderForUser = AdminLinkProviderForUser'
  { -- | The user pool ID for the user pool.
    AdminLinkProviderForUser -> Text
userPoolId :: Prelude.Text,
    -- | The existing user in the user pool that you want to assign to the
    -- external IdP user account. This user can be a native (Username +
    -- Password) Amazon Cognito user pools user or a federated user (for
    -- example, a SAML or Facebook user). If the user doesn\'t exist, Amazon
    -- Cognito generates an exception. Amazon Cognito returns this user when
    -- the new user (with the linked IdP attribute) signs in.
    --
    -- For a native username + password user, the @ProviderAttributeValue@ for
    -- the @DestinationUser@ should be the username in the user pool. For a
    -- federated user, it should be the provider-specific @user_id@.
    --
    -- The @ProviderAttributeName@ of the @DestinationUser@ is ignored.
    --
    -- The @ProviderName@ should be set to @Cognito@ for users in Cognito user
    -- pools.
    --
    -- All attributes in the DestinationUser profile must be mutable. If you
    -- have assigned the user any immutable custom attributes, the operation
    -- won\'t succeed.
    AdminLinkProviderForUser -> ProviderUserIdentifierType
destinationUser :: ProviderUserIdentifierType,
    -- | An external IdP account for a user who doesn\'t exist yet in the user
    -- pool. This user must be a federated user (for example, a SAML or
    -- Facebook user), not another native user.
    --
    -- If the @SourceUser@ is using a federated social IdP, such as Facebook,
    -- Google, or Login with Amazon, you must set the @ProviderAttributeName@
    -- to @Cognito_Subject@. For social IdPs, the @ProviderName@ will be
    -- @Facebook@, @Google@, or @LoginWithAmazon@, and Amazon Cognito will
    -- automatically parse the Facebook, Google, and Login with Amazon tokens
    -- for @id@, @sub@, and @user_id@, respectively. The
    -- @ProviderAttributeValue@ for the user must be the same value as the
    -- @id@, @sub@, or @user_id@ value found in the social IdP token.
    --
    -- For SAML, the @ProviderAttributeName@ can be any value that matches a
    -- claim in the SAML assertion. If you want to link SAML users based on the
    -- subject of the SAML assertion, you should map the subject to a claim
    -- through the SAML IdP and submit that claim name as the
    -- @ProviderAttributeName@. If you set @ProviderAttributeName@ to
    -- @Cognito_Subject@, Amazon Cognito will automatically parse the default
    -- unique identifier found in the subject from the SAML token.
    AdminLinkProviderForUser -> ProviderUserIdentifierType
sourceUser :: ProviderUserIdentifierType
  }
  deriving (AdminLinkProviderForUser -> AdminLinkProviderForUser -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdminLinkProviderForUser -> AdminLinkProviderForUser -> Bool
$c/= :: AdminLinkProviderForUser -> AdminLinkProviderForUser -> Bool
== :: AdminLinkProviderForUser -> AdminLinkProviderForUser -> Bool
$c== :: AdminLinkProviderForUser -> AdminLinkProviderForUser -> Bool
Prelude.Eq, ReadPrec [AdminLinkProviderForUser]
ReadPrec AdminLinkProviderForUser
Int -> ReadS AdminLinkProviderForUser
ReadS [AdminLinkProviderForUser]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AdminLinkProviderForUser]
$creadListPrec :: ReadPrec [AdminLinkProviderForUser]
readPrec :: ReadPrec AdminLinkProviderForUser
$creadPrec :: ReadPrec AdminLinkProviderForUser
readList :: ReadS [AdminLinkProviderForUser]
$creadList :: ReadS [AdminLinkProviderForUser]
readsPrec :: Int -> ReadS AdminLinkProviderForUser
$creadsPrec :: Int -> ReadS AdminLinkProviderForUser
Prelude.Read, Int -> AdminLinkProviderForUser -> ShowS
[AdminLinkProviderForUser] -> ShowS
AdminLinkProviderForUser -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdminLinkProviderForUser] -> ShowS
$cshowList :: [AdminLinkProviderForUser] -> ShowS
show :: AdminLinkProviderForUser -> String
$cshow :: AdminLinkProviderForUser -> String
showsPrec :: Int -> AdminLinkProviderForUser -> ShowS
$cshowsPrec :: Int -> AdminLinkProviderForUser -> ShowS
Prelude.Show, forall x.
Rep AdminLinkProviderForUser x -> AdminLinkProviderForUser
forall x.
AdminLinkProviderForUser -> Rep AdminLinkProviderForUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AdminLinkProviderForUser x -> AdminLinkProviderForUser
$cfrom :: forall x.
AdminLinkProviderForUser -> Rep AdminLinkProviderForUser x
Prelude.Generic)

-- |
-- Create a value of 'AdminLinkProviderForUser' 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:
--
-- 'userPoolId', 'adminLinkProviderForUser_userPoolId' - The user pool ID for the user pool.
--
-- 'destinationUser', 'adminLinkProviderForUser_destinationUser' - The existing user in the user pool that you want to assign to the
-- external IdP user account. This user can be a native (Username +
-- Password) Amazon Cognito user pools user or a federated user (for
-- example, a SAML or Facebook user). If the user doesn\'t exist, Amazon
-- Cognito generates an exception. Amazon Cognito returns this user when
-- the new user (with the linked IdP attribute) signs in.
--
-- For a native username + password user, the @ProviderAttributeValue@ for
-- the @DestinationUser@ should be the username in the user pool. For a
-- federated user, it should be the provider-specific @user_id@.
--
-- The @ProviderAttributeName@ of the @DestinationUser@ is ignored.
--
-- The @ProviderName@ should be set to @Cognito@ for users in Cognito user
-- pools.
--
-- All attributes in the DestinationUser profile must be mutable. If you
-- have assigned the user any immutable custom attributes, the operation
-- won\'t succeed.
--
-- 'sourceUser', 'adminLinkProviderForUser_sourceUser' - An external IdP account for a user who doesn\'t exist yet in the user
-- pool. This user must be a federated user (for example, a SAML or
-- Facebook user), not another native user.
--
-- If the @SourceUser@ is using a federated social IdP, such as Facebook,
-- Google, or Login with Amazon, you must set the @ProviderAttributeName@
-- to @Cognito_Subject@. For social IdPs, the @ProviderName@ will be
-- @Facebook@, @Google@, or @LoginWithAmazon@, and Amazon Cognito will
-- automatically parse the Facebook, Google, and Login with Amazon tokens
-- for @id@, @sub@, and @user_id@, respectively. The
-- @ProviderAttributeValue@ for the user must be the same value as the
-- @id@, @sub@, or @user_id@ value found in the social IdP token.
--
-- For SAML, the @ProviderAttributeName@ can be any value that matches a
-- claim in the SAML assertion. If you want to link SAML users based on the
-- subject of the SAML assertion, you should map the subject to a claim
-- through the SAML IdP and submit that claim name as the
-- @ProviderAttributeName@. If you set @ProviderAttributeName@ to
-- @Cognito_Subject@, Amazon Cognito will automatically parse the default
-- unique identifier found in the subject from the SAML token.
newAdminLinkProviderForUser ::
  -- | 'userPoolId'
  Prelude.Text ->
  -- | 'destinationUser'
  ProviderUserIdentifierType ->
  -- | 'sourceUser'
  ProviderUserIdentifierType ->
  AdminLinkProviderForUser
newAdminLinkProviderForUser :: Text
-> ProviderUserIdentifierType
-> ProviderUserIdentifierType
-> AdminLinkProviderForUser
newAdminLinkProviderForUser
  Text
pUserPoolId_
  ProviderUserIdentifierType
pDestinationUser_
  ProviderUserIdentifierType
pSourceUser_ =
    AdminLinkProviderForUser'
      { $sel:userPoolId:AdminLinkProviderForUser' :: Text
userPoolId =
          Text
pUserPoolId_,
        $sel:destinationUser:AdminLinkProviderForUser' :: ProviderUserIdentifierType
destinationUser = ProviderUserIdentifierType
pDestinationUser_,
        $sel:sourceUser:AdminLinkProviderForUser' :: ProviderUserIdentifierType
sourceUser = ProviderUserIdentifierType
pSourceUser_
      }

-- | The user pool ID for the user pool.
adminLinkProviderForUser_userPoolId :: Lens.Lens' AdminLinkProviderForUser Prelude.Text
adminLinkProviderForUser_userPoolId :: Lens' AdminLinkProviderForUser Text
adminLinkProviderForUser_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminLinkProviderForUser' {Text
userPoolId :: Text
$sel:userPoolId:AdminLinkProviderForUser' :: AdminLinkProviderForUser -> Text
userPoolId} -> Text
userPoolId) (\s :: AdminLinkProviderForUser
s@AdminLinkProviderForUser' {} Text
a -> AdminLinkProviderForUser
s {$sel:userPoolId:AdminLinkProviderForUser' :: Text
userPoolId = Text
a} :: AdminLinkProviderForUser)

-- | The existing user in the user pool that you want to assign to the
-- external IdP user account. This user can be a native (Username +
-- Password) Amazon Cognito user pools user or a federated user (for
-- example, a SAML or Facebook user). If the user doesn\'t exist, Amazon
-- Cognito generates an exception. Amazon Cognito returns this user when
-- the new user (with the linked IdP attribute) signs in.
--
-- For a native username + password user, the @ProviderAttributeValue@ for
-- the @DestinationUser@ should be the username in the user pool. For a
-- federated user, it should be the provider-specific @user_id@.
--
-- The @ProviderAttributeName@ of the @DestinationUser@ is ignored.
--
-- The @ProviderName@ should be set to @Cognito@ for users in Cognito user
-- pools.
--
-- All attributes in the DestinationUser profile must be mutable. If you
-- have assigned the user any immutable custom attributes, the operation
-- won\'t succeed.
adminLinkProviderForUser_destinationUser :: Lens.Lens' AdminLinkProviderForUser ProviderUserIdentifierType
adminLinkProviderForUser_destinationUser :: Lens' AdminLinkProviderForUser ProviderUserIdentifierType
adminLinkProviderForUser_destinationUser = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminLinkProviderForUser' {ProviderUserIdentifierType
destinationUser :: ProviderUserIdentifierType
$sel:destinationUser:AdminLinkProviderForUser' :: AdminLinkProviderForUser -> ProviderUserIdentifierType
destinationUser} -> ProviderUserIdentifierType
destinationUser) (\s :: AdminLinkProviderForUser
s@AdminLinkProviderForUser' {} ProviderUserIdentifierType
a -> AdminLinkProviderForUser
s {$sel:destinationUser:AdminLinkProviderForUser' :: ProviderUserIdentifierType
destinationUser = ProviderUserIdentifierType
a} :: AdminLinkProviderForUser)

-- | An external IdP account for a user who doesn\'t exist yet in the user
-- pool. This user must be a federated user (for example, a SAML or
-- Facebook user), not another native user.
--
-- If the @SourceUser@ is using a federated social IdP, such as Facebook,
-- Google, or Login with Amazon, you must set the @ProviderAttributeName@
-- to @Cognito_Subject@. For social IdPs, the @ProviderName@ will be
-- @Facebook@, @Google@, or @LoginWithAmazon@, and Amazon Cognito will
-- automatically parse the Facebook, Google, and Login with Amazon tokens
-- for @id@, @sub@, and @user_id@, respectively. The
-- @ProviderAttributeValue@ for the user must be the same value as the
-- @id@, @sub@, or @user_id@ value found in the social IdP token.
--
-- For SAML, the @ProviderAttributeName@ can be any value that matches a
-- claim in the SAML assertion. If you want to link SAML users based on the
-- subject of the SAML assertion, you should map the subject to a claim
-- through the SAML IdP and submit that claim name as the
-- @ProviderAttributeName@. If you set @ProviderAttributeName@ to
-- @Cognito_Subject@, Amazon Cognito will automatically parse the default
-- unique identifier found in the subject from the SAML token.
adminLinkProviderForUser_sourceUser :: Lens.Lens' AdminLinkProviderForUser ProviderUserIdentifierType
adminLinkProviderForUser_sourceUser :: Lens' AdminLinkProviderForUser ProviderUserIdentifierType
adminLinkProviderForUser_sourceUser = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminLinkProviderForUser' {ProviderUserIdentifierType
sourceUser :: ProviderUserIdentifierType
$sel:sourceUser:AdminLinkProviderForUser' :: AdminLinkProviderForUser -> ProviderUserIdentifierType
sourceUser} -> ProviderUserIdentifierType
sourceUser) (\s :: AdminLinkProviderForUser
s@AdminLinkProviderForUser' {} ProviderUserIdentifierType
a -> AdminLinkProviderForUser
s {$sel:sourceUser:AdminLinkProviderForUser' :: ProviderUserIdentifierType
sourceUser = ProviderUserIdentifierType
a} :: AdminLinkProviderForUser)

instance Core.AWSRequest AdminLinkProviderForUser where
  type
    AWSResponse AdminLinkProviderForUser =
      AdminLinkProviderForUserResponse
  request :: (Service -> Service)
-> AdminLinkProviderForUser -> Request AdminLinkProviderForUser
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 AdminLinkProviderForUser
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AdminLinkProviderForUser)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> AdminLinkProviderForUserResponse
AdminLinkProviderForUserResponse'
            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))
      )

instance Prelude.Hashable AdminLinkProviderForUser where
  hashWithSalt :: Int -> AdminLinkProviderForUser -> Int
hashWithSalt Int
_salt AdminLinkProviderForUser' {Text
ProviderUserIdentifierType
sourceUser :: ProviderUserIdentifierType
destinationUser :: ProviderUserIdentifierType
userPoolId :: Text
$sel:sourceUser:AdminLinkProviderForUser' :: AdminLinkProviderForUser -> ProviderUserIdentifierType
$sel:destinationUser:AdminLinkProviderForUser' :: AdminLinkProviderForUser -> ProviderUserIdentifierType
$sel:userPoolId:AdminLinkProviderForUser' :: AdminLinkProviderForUser -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userPoolId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ProviderUserIdentifierType
destinationUser
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ProviderUserIdentifierType
sourceUser

instance Prelude.NFData AdminLinkProviderForUser where
  rnf :: AdminLinkProviderForUser -> ()
rnf AdminLinkProviderForUser' {Text
ProviderUserIdentifierType
sourceUser :: ProviderUserIdentifierType
destinationUser :: ProviderUserIdentifierType
userPoolId :: Text
$sel:sourceUser:AdminLinkProviderForUser' :: AdminLinkProviderForUser -> ProviderUserIdentifierType
$sel:destinationUser:AdminLinkProviderForUser' :: AdminLinkProviderForUser -> ProviderUserIdentifierType
$sel:userPoolId:AdminLinkProviderForUser' :: AdminLinkProviderForUser -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
userPoolId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ProviderUserIdentifierType
destinationUser
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ProviderUserIdentifierType
sourceUser

instance Data.ToHeaders AdminLinkProviderForUser where
  toHeaders :: AdminLinkProviderForUser -> 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
"AWSCognitoIdentityProviderService.AdminLinkProviderForUser" ::
                          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 AdminLinkProviderForUser where
  toJSON :: AdminLinkProviderForUser -> Value
toJSON AdminLinkProviderForUser' {Text
ProviderUserIdentifierType
sourceUser :: ProviderUserIdentifierType
destinationUser :: ProviderUserIdentifierType
userPoolId :: Text
$sel:sourceUser:AdminLinkProviderForUser' :: AdminLinkProviderForUser -> ProviderUserIdentifierType
$sel:destinationUser:AdminLinkProviderForUser' :: AdminLinkProviderForUser -> ProviderUserIdentifierType
$sel:userPoolId:AdminLinkProviderForUser' :: AdminLinkProviderForUser -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"UserPoolId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userPoolId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"DestinationUser" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ProviderUserIdentifierType
destinationUser),
            forall a. a -> Maybe a
Prelude.Just (Key
"SourceUser" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ProviderUserIdentifierType
sourceUser)
          ]
      )

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

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

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

-- |
-- Create a value of 'AdminLinkProviderForUserResponse' 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', 'adminLinkProviderForUserResponse_httpStatus' - The response's http status code.
newAdminLinkProviderForUserResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AdminLinkProviderForUserResponse
newAdminLinkProviderForUserResponse :: Int -> AdminLinkProviderForUserResponse
newAdminLinkProviderForUserResponse Int
pHttpStatus_ =
  AdminLinkProviderForUserResponse'
    { $sel:httpStatus:AdminLinkProviderForUserResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance
  Prelude.NFData
    AdminLinkProviderForUserResponse
  where
  rnf :: AdminLinkProviderForUserResponse -> ()
rnf AdminLinkProviderForUserResponse' {Int
httpStatus :: Int
$sel:httpStatus:AdminLinkProviderForUserResponse' :: AdminLinkProviderForUserResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus