{-# 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.UpdatePrimaryEmailAddress
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the primary email for a user, group, or resource. The current
-- email is moved into the list of aliases (or swapped between an existing
-- alias and the current primary email), and the email provided in the
-- input is promoted as the primary.
module Amazonka.WorkMail.UpdatePrimaryEmailAddress
  ( -- * Creating a Request
    UpdatePrimaryEmailAddress (..),
    newUpdatePrimaryEmailAddress,

    -- * Request Lenses
    updatePrimaryEmailAddress_organizationId,
    updatePrimaryEmailAddress_entityId,
    updatePrimaryEmailAddress_email,

    -- * Destructuring the Response
    UpdatePrimaryEmailAddressResponse (..),
    newUpdatePrimaryEmailAddressResponse,

    -- * Response Lenses
    updatePrimaryEmailAddressResponse_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:/ 'newUpdatePrimaryEmailAddress' smart constructor.
data UpdatePrimaryEmailAddress = UpdatePrimaryEmailAddress'
  { -- | The organization that contains the user, group, or resource to update.
    UpdatePrimaryEmailAddress -> Text
organizationId :: Prelude.Text,
    -- | The user, group, or resource to update.
    UpdatePrimaryEmailAddress -> Text
entityId :: Prelude.Text,
    -- | The value of the email to be updated as primary.
    UpdatePrimaryEmailAddress -> Text
email :: Prelude.Text
  }
  deriving (UpdatePrimaryEmailAddress -> UpdatePrimaryEmailAddress -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdatePrimaryEmailAddress -> UpdatePrimaryEmailAddress -> Bool
$c/= :: UpdatePrimaryEmailAddress -> UpdatePrimaryEmailAddress -> Bool
== :: UpdatePrimaryEmailAddress -> UpdatePrimaryEmailAddress -> Bool
$c== :: UpdatePrimaryEmailAddress -> UpdatePrimaryEmailAddress -> Bool
Prelude.Eq, ReadPrec [UpdatePrimaryEmailAddress]
ReadPrec UpdatePrimaryEmailAddress
Int -> ReadS UpdatePrimaryEmailAddress
ReadS [UpdatePrimaryEmailAddress]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdatePrimaryEmailAddress]
$creadListPrec :: ReadPrec [UpdatePrimaryEmailAddress]
readPrec :: ReadPrec UpdatePrimaryEmailAddress
$creadPrec :: ReadPrec UpdatePrimaryEmailAddress
readList :: ReadS [UpdatePrimaryEmailAddress]
$creadList :: ReadS [UpdatePrimaryEmailAddress]
readsPrec :: Int -> ReadS UpdatePrimaryEmailAddress
$creadsPrec :: Int -> ReadS UpdatePrimaryEmailAddress
Prelude.Read, Int -> UpdatePrimaryEmailAddress -> ShowS
[UpdatePrimaryEmailAddress] -> ShowS
UpdatePrimaryEmailAddress -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdatePrimaryEmailAddress] -> ShowS
$cshowList :: [UpdatePrimaryEmailAddress] -> ShowS
show :: UpdatePrimaryEmailAddress -> String
$cshow :: UpdatePrimaryEmailAddress -> String
showsPrec :: Int -> UpdatePrimaryEmailAddress -> ShowS
$cshowsPrec :: Int -> UpdatePrimaryEmailAddress -> ShowS
Prelude.Show, forall x.
Rep UpdatePrimaryEmailAddress x -> UpdatePrimaryEmailAddress
forall x.
UpdatePrimaryEmailAddress -> Rep UpdatePrimaryEmailAddress x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdatePrimaryEmailAddress x -> UpdatePrimaryEmailAddress
$cfrom :: forall x.
UpdatePrimaryEmailAddress -> Rep UpdatePrimaryEmailAddress x
Prelude.Generic)

-- |
-- Create a value of 'UpdatePrimaryEmailAddress' 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', 'updatePrimaryEmailAddress_organizationId' - The organization that contains the user, group, or resource to update.
--
-- 'entityId', 'updatePrimaryEmailAddress_entityId' - The user, group, or resource to update.
--
-- 'email', 'updatePrimaryEmailAddress_email' - The value of the email to be updated as primary.
newUpdatePrimaryEmailAddress ::
  -- | 'organizationId'
  Prelude.Text ->
  -- | 'entityId'
  Prelude.Text ->
  -- | 'email'
  Prelude.Text ->
  UpdatePrimaryEmailAddress
newUpdatePrimaryEmailAddress :: Text -> Text -> Text -> UpdatePrimaryEmailAddress
newUpdatePrimaryEmailAddress
  Text
pOrganizationId_
  Text
pEntityId_
  Text
pEmail_ =
    UpdatePrimaryEmailAddress'
      { $sel:organizationId:UpdatePrimaryEmailAddress' :: Text
organizationId =
          Text
pOrganizationId_,
        $sel:entityId:UpdatePrimaryEmailAddress' :: Text
entityId = Text
pEntityId_,
        $sel:email:UpdatePrimaryEmailAddress' :: Text
email = Text
pEmail_
      }

-- | The organization that contains the user, group, or resource to update.
updatePrimaryEmailAddress_organizationId :: Lens.Lens' UpdatePrimaryEmailAddress Prelude.Text
updatePrimaryEmailAddress_organizationId :: Lens' UpdatePrimaryEmailAddress Text
updatePrimaryEmailAddress_organizationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePrimaryEmailAddress' {Text
organizationId :: Text
$sel:organizationId:UpdatePrimaryEmailAddress' :: UpdatePrimaryEmailAddress -> Text
organizationId} -> Text
organizationId) (\s :: UpdatePrimaryEmailAddress
s@UpdatePrimaryEmailAddress' {} Text
a -> UpdatePrimaryEmailAddress
s {$sel:organizationId:UpdatePrimaryEmailAddress' :: Text
organizationId = Text
a} :: UpdatePrimaryEmailAddress)

-- | The user, group, or resource to update.
updatePrimaryEmailAddress_entityId :: Lens.Lens' UpdatePrimaryEmailAddress Prelude.Text
updatePrimaryEmailAddress_entityId :: Lens' UpdatePrimaryEmailAddress Text
updatePrimaryEmailAddress_entityId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePrimaryEmailAddress' {Text
entityId :: Text
$sel:entityId:UpdatePrimaryEmailAddress' :: UpdatePrimaryEmailAddress -> Text
entityId} -> Text
entityId) (\s :: UpdatePrimaryEmailAddress
s@UpdatePrimaryEmailAddress' {} Text
a -> UpdatePrimaryEmailAddress
s {$sel:entityId:UpdatePrimaryEmailAddress' :: Text
entityId = Text
a} :: UpdatePrimaryEmailAddress)

-- | The value of the email to be updated as primary.
updatePrimaryEmailAddress_email :: Lens.Lens' UpdatePrimaryEmailAddress Prelude.Text
updatePrimaryEmailAddress_email :: Lens' UpdatePrimaryEmailAddress Text
updatePrimaryEmailAddress_email = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePrimaryEmailAddress' {Text
email :: Text
$sel:email:UpdatePrimaryEmailAddress' :: UpdatePrimaryEmailAddress -> Text
email} -> Text
email) (\s :: UpdatePrimaryEmailAddress
s@UpdatePrimaryEmailAddress' {} Text
a -> UpdatePrimaryEmailAddress
s {$sel:email:UpdatePrimaryEmailAddress' :: Text
email = Text
a} :: UpdatePrimaryEmailAddress)

instance Core.AWSRequest UpdatePrimaryEmailAddress where
  type
    AWSResponse UpdatePrimaryEmailAddress =
      UpdatePrimaryEmailAddressResponse
  request :: (Service -> Service)
-> UpdatePrimaryEmailAddress -> Request UpdatePrimaryEmailAddress
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 UpdatePrimaryEmailAddress
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdatePrimaryEmailAddress)))
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 -> UpdatePrimaryEmailAddressResponse
UpdatePrimaryEmailAddressResponse'
            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 UpdatePrimaryEmailAddress where
  hashWithSalt :: Int -> UpdatePrimaryEmailAddress -> Int
hashWithSalt Int
_salt UpdatePrimaryEmailAddress' {Text
email :: Text
entityId :: Text
organizationId :: Text
$sel:email:UpdatePrimaryEmailAddress' :: UpdatePrimaryEmailAddress -> Text
$sel:entityId:UpdatePrimaryEmailAddress' :: UpdatePrimaryEmailAddress -> Text
$sel:organizationId:UpdatePrimaryEmailAddress' :: UpdatePrimaryEmailAddress -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
organizationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
entityId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
email

instance Prelude.NFData UpdatePrimaryEmailAddress where
  rnf :: UpdatePrimaryEmailAddress -> ()
rnf UpdatePrimaryEmailAddress' {Text
email :: Text
entityId :: Text
organizationId :: Text
$sel:email:UpdatePrimaryEmailAddress' :: UpdatePrimaryEmailAddress -> Text
$sel:entityId:UpdatePrimaryEmailAddress' :: UpdatePrimaryEmailAddress -> Text
$sel:organizationId:UpdatePrimaryEmailAddress' :: UpdatePrimaryEmailAddress -> 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
entityId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
email

instance Data.ToHeaders UpdatePrimaryEmailAddress where
  toHeaders :: UpdatePrimaryEmailAddress -> 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.UpdatePrimaryEmailAddress" ::
                          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 UpdatePrimaryEmailAddress where
  toJSON :: UpdatePrimaryEmailAddress -> Value
toJSON UpdatePrimaryEmailAddress' {Text
email :: Text
entityId :: Text
organizationId :: Text
$sel:email:UpdatePrimaryEmailAddress' :: UpdatePrimaryEmailAddress -> Text
$sel:entityId:UpdatePrimaryEmailAddress' :: UpdatePrimaryEmailAddress -> Text
$sel:organizationId:UpdatePrimaryEmailAddress' :: UpdatePrimaryEmailAddress -> 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
"EntityId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
entityId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Email" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
email)
          ]
      )

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

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

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

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

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

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