{-# 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.WorkMail.AssumeImpersonationRole
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Assumes an impersonation role for the given WorkMail organization. This
-- method returns an authentication token you can use to make impersonated
-- calls.
module Amazonka.WorkMail.AssumeImpersonationRole
  ( -- * Creating a Request
    AssumeImpersonationRole (..),
    newAssumeImpersonationRole,

    -- * Request Lenses
    assumeImpersonationRole_organizationId,
    assumeImpersonationRole_impersonationRoleId,

    -- * Destructuring the Response
    AssumeImpersonationRoleResponse (..),
    newAssumeImpersonationRoleResponse,

    -- * Response Lenses
    assumeImpersonationRoleResponse_expiresIn,
    assumeImpersonationRoleResponse_token,
    assumeImpersonationRoleResponse_httpStatus,
  )
where

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

-- | /See:/ 'newAssumeImpersonationRole' smart constructor.
data AssumeImpersonationRole = AssumeImpersonationRole'
  { -- | The WorkMail organization under which the impersonation role will be
    -- assumed.
    AssumeImpersonationRole -> Text
organizationId :: Prelude.Text,
    -- | The impersonation role ID to assume.
    AssumeImpersonationRole -> Text
impersonationRoleId :: Prelude.Text
  }
  deriving (AssumeImpersonationRole -> AssumeImpersonationRole -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssumeImpersonationRole -> AssumeImpersonationRole -> Bool
$c/= :: AssumeImpersonationRole -> AssumeImpersonationRole -> Bool
== :: AssumeImpersonationRole -> AssumeImpersonationRole -> Bool
$c== :: AssumeImpersonationRole -> AssumeImpersonationRole -> Bool
Prelude.Eq, ReadPrec [AssumeImpersonationRole]
ReadPrec AssumeImpersonationRole
Int -> ReadS AssumeImpersonationRole
ReadS [AssumeImpersonationRole]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssumeImpersonationRole]
$creadListPrec :: ReadPrec [AssumeImpersonationRole]
readPrec :: ReadPrec AssumeImpersonationRole
$creadPrec :: ReadPrec AssumeImpersonationRole
readList :: ReadS [AssumeImpersonationRole]
$creadList :: ReadS [AssumeImpersonationRole]
readsPrec :: Int -> ReadS AssumeImpersonationRole
$creadsPrec :: Int -> ReadS AssumeImpersonationRole
Prelude.Read, Int -> AssumeImpersonationRole -> ShowS
[AssumeImpersonationRole] -> ShowS
AssumeImpersonationRole -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssumeImpersonationRole] -> ShowS
$cshowList :: [AssumeImpersonationRole] -> ShowS
show :: AssumeImpersonationRole -> String
$cshow :: AssumeImpersonationRole -> String
showsPrec :: Int -> AssumeImpersonationRole -> ShowS
$cshowsPrec :: Int -> AssumeImpersonationRole -> ShowS
Prelude.Show, forall x. Rep AssumeImpersonationRole x -> AssumeImpersonationRole
forall x. AssumeImpersonationRole -> Rep AssumeImpersonationRole x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssumeImpersonationRole x -> AssumeImpersonationRole
$cfrom :: forall x. AssumeImpersonationRole -> Rep AssumeImpersonationRole x
Prelude.Generic)

-- |
-- Create a value of 'AssumeImpersonationRole' 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:
--
-- 'organizationId', 'assumeImpersonationRole_organizationId' - The WorkMail organization under which the impersonation role will be
-- assumed.
--
-- 'impersonationRoleId', 'assumeImpersonationRole_impersonationRoleId' - The impersonation role ID to assume.
newAssumeImpersonationRole ::
  -- | 'organizationId'
  Prelude.Text ->
  -- | 'impersonationRoleId'
  Prelude.Text ->
  AssumeImpersonationRole
newAssumeImpersonationRole :: Text -> Text -> AssumeImpersonationRole
newAssumeImpersonationRole
  Text
pOrganizationId_
  Text
pImpersonationRoleId_ =
    AssumeImpersonationRole'
      { $sel:organizationId:AssumeImpersonationRole' :: Text
organizationId =
          Text
pOrganizationId_,
        $sel:impersonationRoleId:AssumeImpersonationRole' :: Text
impersonationRoleId = Text
pImpersonationRoleId_
      }

-- | The WorkMail organization under which the impersonation role will be
-- assumed.
assumeImpersonationRole_organizationId :: Lens.Lens' AssumeImpersonationRole Prelude.Text
assumeImpersonationRole_organizationId :: Lens' AssumeImpersonationRole Text
assumeImpersonationRole_organizationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssumeImpersonationRole' {Text
organizationId :: Text
$sel:organizationId:AssumeImpersonationRole' :: AssumeImpersonationRole -> Text
organizationId} -> Text
organizationId) (\s :: AssumeImpersonationRole
s@AssumeImpersonationRole' {} Text
a -> AssumeImpersonationRole
s {$sel:organizationId:AssumeImpersonationRole' :: Text
organizationId = Text
a} :: AssumeImpersonationRole)

-- | The impersonation role ID to assume.
assumeImpersonationRole_impersonationRoleId :: Lens.Lens' AssumeImpersonationRole Prelude.Text
assumeImpersonationRole_impersonationRoleId :: Lens' AssumeImpersonationRole Text
assumeImpersonationRole_impersonationRoleId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssumeImpersonationRole' {Text
impersonationRoleId :: Text
$sel:impersonationRoleId:AssumeImpersonationRole' :: AssumeImpersonationRole -> Text
impersonationRoleId} -> Text
impersonationRoleId) (\s :: AssumeImpersonationRole
s@AssumeImpersonationRole' {} Text
a -> AssumeImpersonationRole
s {$sel:impersonationRoleId:AssumeImpersonationRole' :: Text
impersonationRoleId = Text
a} :: AssumeImpersonationRole)

instance Core.AWSRequest AssumeImpersonationRole where
  type
    AWSResponse AssumeImpersonationRole =
      AssumeImpersonationRoleResponse
  request :: (Service -> Service)
-> AssumeImpersonationRole -> Request AssumeImpersonationRole
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 AssumeImpersonationRole
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AssumeImpersonationRole)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Integer
-> Maybe Text -> Int -> AssumeImpersonationRoleResponse
AssumeImpersonationRoleResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ExpiresIn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Token")
            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 AssumeImpersonationRole where
  hashWithSalt :: Int -> AssumeImpersonationRole -> Int
hashWithSalt Int
_salt AssumeImpersonationRole' {Text
impersonationRoleId :: Text
organizationId :: Text
$sel:impersonationRoleId:AssumeImpersonationRole' :: AssumeImpersonationRole -> Text
$sel:organizationId:AssumeImpersonationRole' :: AssumeImpersonationRole -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
organizationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
impersonationRoleId

instance Prelude.NFData AssumeImpersonationRole where
  rnf :: AssumeImpersonationRole -> ()
rnf AssumeImpersonationRole' {Text
impersonationRoleId :: Text
organizationId :: Text
$sel:impersonationRoleId:AssumeImpersonationRole' :: AssumeImpersonationRole -> Text
$sel:organizationId:AssumeImpersonationRole' :: AssumeImpersonationRole -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
organizationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
impersonationRoleId

instance Data.ToHeaders AssumeImpersonationRole where
  toHeaders :: AssumeImpersonationRole -> 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
"WorkMailService.AssumeImpersonationRole" ::
                          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 AssumeImpersonationRole where
  toJSON :: AssumeImpersonationRole -> Value
toJSON AssumeImpersonationRole' {Text
impersonationRoleId :: Text
organizationId :: Text
$sel:impersonationRoleId:AssumeImpersonationRole' :: AssumeImpersonationRole -> Text
$sel:organizationId:AssumeImpersonationRole' :: AssumeImpersonationRole -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"OrganizationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
organizationId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ImpersonationRoleId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
impersonationRoleId)
          ]
      )

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

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

-- | /See:/ 'newAssumeImpersonationRoleResponse' smart constructor.
data AssumeImpersonationRoleResponse = AssumeImpersonationRoleResponse'
  { -- | The authentication token\'s validity, in seconds.
    AssumeImpersonationRoleResponse -> Maybe Integer
expiresIn :: Prelude.Maybe Prelude.Integer,
    -- | The authentication token for the impersonation role.
    AssumeImpersonationRoleResponse -> Maybe Text
token :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    AssumeImpersonationRoleResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AssumeImpersonationRoleResponse
-> AssumeImpersonationRoleResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssumeImpersonationRoleResponse
-> AssumeImpersonationRoleResponse -> Bool
$c/= :: AssumeImpersonationRoleResponse
-> AssumeImpersonationRoleResponse -> Bool
== :: AssumeImpersonationRoleResponse
-> AssumeImpersonationRoleResponse -> Bool
$c== :: AssumeImpersonationRoleResponse
-> AssumeImpersonationRoleResponse -> Bool
Prelude.Eq, ReadPrec [AssumeImpersonationRoleResponse]
ReadPrec AssumeImpersonationRoleResponse
Int -> ReadS AssumeImpersonationRoleResponse
ReadS [AssumeImpersonationRoleResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssumeImpersonationRoleResponse]
$creadListPrec :: ReadPrec [AssumeImpersonationRoleResponse]
readPrec :: ReadPrec AssumeImpersonationRoleResponse
$creadPrec :: ReadPrec AssumeImpersonationRoleResponse
readList :: ReadS [AssumeImpersonationRoleResponse]
$creadList :: ReadS [AssumeImpersonationRoleResponse]
readsPrec :: Int -> ReadS AssumeImpersonationRoleResponse
$creadsPrec :: Int -> ReadS AssumeImpersonationRoleResponse
Prelude.Read, Int -> AssumeImpersonationRoleResponse -> ShowS
[AssumeImpersonationRoleResponse] -> ShowS
AssumeImpersonationRoleResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssumeImpersonationRoleResponse] -> ShowS
$cshowList :: [AssumeImpersonationRoleResponse] -> ShowS
show :: AssumeImpersonationRoleResponse -> String
$cshow :: AssumeImpersonationRoleResponse -> String
showsPrec :: Int -> AssumeImpersonationRoleResponse -> ShowS
$cshowsPrec :: Int -> AssumeImpersonationRoleResponse -> ShowS
Prelude.Show, forall x.
Rep AssumeImpersonationRoleResponse x
-> AssumeImpersonationRoleResponse
forall x.
AssumeImpersonationRoleResponse
-> Rep AssumeImpersonationRoleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssumeImpersonationRoleResponse x
-> AssumeImpersonationRoleResponse
$cfrom :: forall x.
AssumeImpersonationRoleResponse
-> Rep AssumeImpersonationRoleResponse x
Prelude.Generic)

-- |
-- Create a value of 'AssumeImpersonationRoleResponse' 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:
--
-- 'expiresIn', 'assumeImpersonationRoleResponse_expiresIn' - The authentication token\'s validity, in seconds.
--
-- 'token', 'assumeImpersonationRoleResponse_token' - The authentication token for the impersonation role.
--
-- 'httpStatus', 'assumeImpersonationRoleResponse_httpStatus' - The response's http status code.
newAssumeImpersonationRoleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AssumeImpersonationRoleResponse
newAssumeImpersonationRoleResponse :: Int -> AssumeImpersonationRoleResponse
newAssumeImpersonationRoleResponse Int
pHttpStatus_ =
  AssumeImpersonationRoleResponse'
    { $sel:expiresIn:AssumeImpersonationRoleResponse' :: Maybe Integer
expiresIn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:token:AssumeImpersonationRoleResponse' :: Maybe Text
token = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AssumeImpersonationRoleResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The authentication token\'s validity, in seconds.
assumeImpersonationRoleResponse_expiresIn :: Lens.Lens' AssumeImpersonationRoleResponse (Prelude.Maybe Prelude.Integer)
assumeImpersonationRoleResponse_expiresIn :: Lens' AssumeImpersonationRoleResponse (Maybe Integer)
assumeImpersonationRoleResponse_expiresIn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssumeImpersonationRoleResponse' {Maybe Integer
expiresIn :: Maybe Integer
$sel:expiresIn:AssumeImpersonationRoleResponse' :: AssumeImpersonationRoleResponse -> Maybe Integer
expiresIn} -> Maybe Integer
expiresIn) (\s :: AssumeImpersonationRoleResponse
s@AssumeImpersonationRoleResponse' {} Maybe Integer
a -> AssumeImpersonationRoleResponse
s {$sel:expiresIn:AssumeImpersonationRoleResponse' :: Maybe Integer
expiresIn = Maybe Integer
a} :: AssumeImpersonationRoleResponse)

-- | The authentication token for the impersonation role.
assumeImpersonationRoleResponse_token :: Lens.Lens' AssumeImpersonationRoleResponse (Prelude.Maybe Prelude.Text)
assumeImpersonationRoleResponse_token :: Lens' AssumeImpersonationRoleResponse (Maybe Text)
assumeImpersonationRoleResponse_token = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssumeImpersonationRoleResponse' {Maybe Text
token :: Maybe Text
$sel:token:AssumeImpersonationRoleResponse' :: AssumeImpersonationRoleResponse -> Maybe Text
token} -> Maybe Text
token) (\s :: AssumeImpersonationRoleResponse
s@AssumeImpersonationRoleResponse' {} Maybe Text
a -> AssumeImpersonationRoleResponse
s {$sel:token:AssumeImpersonationRoleResponse' :: Maybe Text
token = Maybe Text
a} :: AssumeImpersonationRoleResponse)

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

instance
  Prelude.NFData
    AssumeImpersonationRoleResponse
  where
  rnf :: AssumeImpersonationRoleResponse -> ()
rnf AssumeImpersonationRoleResponse' {Int
Maybe Integer
Maybe Text
httpStatus :: Int
token :: Maybe Text
expiresIn :: Maybe Integer
$sel:httpStatus:AssumeImpersonationRoleResponse' :: AssumeImpersonationRoleResponse -> Int
$sel:token:AssumeImpersonationRoleResponse' :: AssumeImpersonationRoleResponse -> Maybe Text
$sel:expiresIn:AssumeImpersonationRoleResponse' :: AssumeImpersonationRoleResponse -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
expiresIn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
token
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus