{-# 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.Connect.UpdatePhoneNumber
-- 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 your claimed phone number from its current Amazon Connect
-- instance or traffic distribution group to another Amazon Connect
-- instance or traffic distribution group in the same Amazon Web Services
-- Region.
--
-- You can call
-- <https://docs.aws.amazon.com/connect/latest/APIReference/API_DescribePhoneNumber.html DescribePhoneNumber>
-- API to verify the status of a previous
-- <https://docs.aws.amazon.com/connect/latest/APIReference/API_UpdatePhoneNumber.html UpdatePhoneNumber>
-- operation.
module Amazonka.Connect.UpdatePhoneNumber
  ( -- * Creating a Request
    UpdatePhoneNumber (..),
    newUpdatePhoneNumber,

    -- * Request Lenses
    updatePhoneNumber_clientToken,
    updatePhoneNumber_phoneNumberId,
    updatePhoneNumber_targetArn,

    -- * Destructuring the Response
    UpdatePhoneNumberResponse (..),
    newUpdatePhoneNumberResponse,

    -- * Response Lenses
    updatePhoneNumberResponse_phoneNumberArn,
    updatePhoneNumberResponse_phoneNumberId,
    updatePhoneNumberResponse_httpStatus,
  )
where

import Amazonka.Connect.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:/ 'newUpdatePhoneNumber' smart constructor.
data UpdatePhoneNumber = UpdatePhoneNumber'
  { -- | A unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request. If not provided, the Amazon Web Services SDK
    -- populates this field. For more information about idempotency, see
    -- <https://aws.amazon.com/builders-library/making-retries-safe-with-idempotent-APIs/ Making retries safe with idempotent APIs>.
    UpdatePhoneNumber -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the phone number.
    UpdatePhoneNumber -> Text
phoneNumberId :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) for Amazon Connect instances or traffic
    -- distribution groups that phone numbers are claimed to.
    UpdatePhoneNumber -> Text
targetArn :: Prelude.Text
  }
  deriving (UpdatePhoneNumber -> UpdatePhoneNumber -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdatePhoneNumber -> UpdatePhoneNumber -> Bool
$c/= :: UpdatePhoneNumber -> UpdatePhoneNumber -> Bool
== :: UpdatePhoneNumber -> UpdatePhoneNumber -> Bool
$c== :: UpdatePhoneNumber -> UpdatePhoneNumber -> Bool
Prelude.Eq, ReadPrec [UpdatePhoneNumber]
ReadPrec UpdatePhoneNumber
Int -> ReadS UpdatePhoneNumber
ReadS [UpdatePhoneNumber]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdatePhoneNumber]
$creadListPrec :: ReadPrec [UpdatePhoneNumber]
readPrec :: ReadPrec UpdatePhoneNumber
$creadPrec :: ReadPrec UpdatePhoneNumber
readList :: ReadS [UpdatePhoneNumber]
$creadList :: ReadS [UpdatePhoneNumber]
readsPrec :: Int -> ReadS UpdatePhoneNumber
$creadsPrec :: Int -> ReadS UpdatePhoneNumber
Prelude.Read, Int -> UpdatePhoneNumber -> ShowS
[UpdatePhoneNumber] -> ShowS
UpdatePhoneNumber -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdatePhoneNumber] -> ShowS
$cshowList :: [UpdatePhoneNumber] -> ShowS
show :: UpdatePhoneNumber -> String
$cshow :: UpdatePhoneNumber -> String
showsPrec :: Int -> UpdatePhoneNumber -> ShowS
$cshowsPrec :: Int -> UpdatePhoneNumber -> ShowS
Prelude.Show, forall x. Rep UpdatePhoneNumber x -> UpdatePhoneNumber
forall x. UpdatePhoneNumber -> Rep UpdatePhoneNumber x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdatePhoneNumber x -> UpdatePhoneNumber
$cfrom :: forall x. UpdatePhoneNumber -> Rep UpdatePhoneNumber x
Prelude.Generic)

-- |
-- Create a value of 'UpdatePhoneNumber' 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:
--
-- 'clientToken', 'updatePhoneNumber_clientToken' - A unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. If not provided, the Amazon Web Services SDK
-- populates this field. For more information about idempotency, see
-- <https://aws.amazon.com/builders-library/making-retries-safe-with-idempotent-APIs/ Making retries safe with idempotent APIs>.
--
-- 'phoneNumberId', 'updatePhoneNumber_phoneNumberId' - A unique identifier for the phone number.
--
-- 'targetArn', 'updatePhoneNumber_targetArn' - The Amazon Resource Name (ARN) for Amazon Connect instances or traffic
-- distribution groups that phone numbers are claimed to.
newUpdatePhoneNumber ::
  -- | 'phoneNumberId'
  Prelude.Text ->
  -- | 'targetArn'
  Prelude.Text ->
  UpdatePhoneNumber
newUpdatePhoneNumber :: Text -> Text -> UpdatePhoneNumber
newUpdatePhoneNumber Text
pPhoneNumberId_ Text
pTargetArn_ =
  UpdatePhoneNumber'
    { $sel:clientToken:UpdatePhoneNumber' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:phoneNumberId:UpdatePhoneNumber' :: Text
phoneNumberId = Text
pPhoneNumberId_,
      $sel:targetArn:UpdatePhoneNumber' :: Text
targetArn = Text
pTargetArn_
    }

-- | A unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. If not provided, the Amazon Web Services SDK
-- populates this field. For more information about idempotency, see
-- <https://aws.amazon.com/builders-library/making-retries-safe-with-idempotent-APIs/ Making retries safe with idempotent APIs>.
updatePhoneNumber_clientToken :: Lens.Lens' UpdatePhoneNumber (Prelude.Maybe Prelude.Text)
updatePhoneNumber_clientToken :: Lens' UpdatePhoneNumber (Maybe Text)
updatePhoneNumber_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumber' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: UpdatePhoneNumber
s@UpdatePhoneNumber' {} Maybe Text
a -> UpdatePhoneNumber
s {$sel:clientToken:UpdatePhoneNumber' :: Maybe Text
clientToken = Maybe Text
a} :: UpdatePhoneNumber)

-- | A unique identifier for the phone number.
updatePhoneNumber_phoneNumberId :: Lens.Lens' UpdatePhoneNumber Prelude.Text
updatePhoneNumber_phoneNumberId :: Lens' UpdatePhoneNumber Text
updatePhoneNumber_phoneNumberId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumber' {Text
phoneNumberId :: Text
$sel:phoneNumberId:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
phoneNumberId} -> Text
phoneNumberId) (\s :: UpdatePhoneNumber
s@UpdatePhoneNumber' {} Text
a -> UpdatePhoneNumber
s {$sel:phoneNumberId:UpdatePhoneNumber' :: Text
phoneNumberId = Text
a} :: UpdatePhoneNumber)

-- | The Amazon Resource Name (ARN) for Amazon Connect instances or traffic
-- distribution groups that phone numbers are claimed to.
updatePhoneNumber_targetArn :: Lens.Lens' UpdatePhoneNumber Prelude.Text
updatePhoneNumber_targetArn :: Lens' UpdatePhoneNumber Text
updatePhoneNumber_targetArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumber' {Text
targetArn :: Text
$sel:targetArn:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
targetArn} -> Text
targetArn) (\s :: UpdatePhoneNumber
s@UpdatePhoneNumber' {} Text
a -> UpdatePhoneNumber
s {$sel:targetArn:UpdatePhoneNumber' :: Text
targetArn = Text
a} :: UpdatePhoneNumber)

instance Core.AWSRequest UpdatePhoneNumber where
  type
    AWSResponse UpdatePhoneNumber =
      UpdatePhoneNumberResponse
  request :: (Service -> Service)
-> UpdatePhoneNumber -> Request UpdatePhoneNumber
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdatePhoneNumber
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdatePhoneNumber)))
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 Text -> Maybe Text -> Int -> UpdatePhoneNumberResponse
UpdatePhoneNumberResponse'
            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
"PhoneNumberArn")
            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
"PhoneNumberId")
            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 UpdatePhoneNumber where
  hashWithSalt :: Int -> UpdatePhoneNumber -> Int
hashWithSalt Int
_salt UpdatePhoneNumber' {Maybe Text
Text
targetArn :: Text
phoneNumberId :: Text
clientToken :: Maybe Text
$sel:targetArn:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
$sel:phoneNumberId:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
$sel:clientToken:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
phoneNumberId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
targetArn

instance Prelude.NFData UpdatePhoneNumber where
  rnf :: UpdatePhoneNumber -> ()
rnf UpdatePhoneNumber' {Maybe Text
Text
targetArn :: Text
phoneNumberId :: Text
clientToken :: Maybe Text
$sel:targetArn:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
$sel:phoneNumberId:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
$sel:clientToken:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
phoneNumberId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
targetArn

instance Data.ToHeaders UpdatePhoneNumber where
  toHeaders :: UpdatePhoneNumber -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdatePhoneNumber where
  toJSON :: UpdatePhoneNumber -> Value
toJSON UpdatePhoneNumber' {Maybe Text
Text
targetArn :: Text
phoneNumberId :: Text
clientToken :: Maybe Text
$sel:targetArn:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
$sel:phoneNumberId:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
$sel:clientToken:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
clientToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"TargetArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
targetArn)
          ]
      )

instance Data.ToPath UpdatePhoneNumber where
  toPath :: UpdatePhoneNumber -> ByteString
toPath UpdatePhoneNumber' {Maybe Text
Text
targetArn :: Text
phoneNumberId :: Text
clientToken :: Maybe Text
$sel:targetArn:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
$sel:phoneNumberId:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
$sel:clientToken:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/phone-number/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
phoneNumberId]

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

-- | /See:/ 'newUpdatePhoneNumberResponse' smart constructor.
data UpdatePhoneNumberResponse = UpdatePhoneNumberResponse'
  { -- | The Amazon Resource Name (ARN) of the phone number.
    UpdatePhoneNumberResponse -> Maybe Text
phoneNumberArn :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the phone number.
    UpdatePhoneNumberResponse -> Maybe Text
phoneNumberId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdatePhoneNumberResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdatePhoneNumberResponse -> UpdatePhoneNumberResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdatePhoneNumberResponse -> UpdatePhoneNumberResponse -> Bool
$c/= :: UpdatePhoneNumberResponse -> UpdatePhoneNumberResponse -> Bool
== :: UpdatePhoneNumberResponse -> UpdatePhoneNumberResponse -> Bool
$c== :: UpdatePhoneNumberResponse -> UpdatePhoneNumberResponse -> Bool
Prelude.Eq, ReadPrec [UpdatePhoneNumberResponse]
ReadPrec UpdatePhoneNumberResponse
Int -> ReadS UpdatePhoneNumberResponse
ReadS [UpdatePhoneNumberResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdatePhoneNumberResponse]
$creadListPrec :: ReadPrec [UpdatePhoneNumberResponse]
readPrec :: ReadPrec UpdatePhoneNumberResponse
$creadPrec :: ReadPrec UpdatePhoneNumberResponse
readList :: ReadS [UpdatePhoneNumberResponse]
$creadList :: ReadS [UpdatePhoneNumberResponse]
readsPrec :: Int -> ReadS UpdatePhoneNumberResponse
$creadsPrec :: Int -> ReadS UpdatePhoneNumberResponse
Prelude.Read, Int -> UpdatePhoneNumberResponse -> ShowS
[UpdatePhoneNumberResponse] -> ShowS
UpdatePhoneNumberResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdatePhoneNumberResponse] -> ShowS
$cshowList :: [UpdatePhoneNumberResponse] -> ShowS
show :: UpdatePhoneNumberResponse -> String
$cshow :: UpdatePhoneNumberResponse -> String
showsPrec :: Int -> UpdatePhoneNumberResponse -> ShowS
$cshowsPrec :: Int -> UpdatePhoneNumberResponse -> ShowS
Prelude.Show, forall x.
Rep UpdatePhoneNumberResponse x -> UpdatePhoneNumberResponse
forall x.
UpdatePhoneNumberResponse -> Rep UpdatePhoneNumberResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdatePhoneNumberResponse x -> UpdatePhoneNumberResponse
$cfrom :: forall x.
UpdatePhoneNumberResponse -> Rep UpdatePhoneNumberResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdatePhoneNumberResponse' 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:
--
-- 'phoneNumberArn', 'updatePhoneNumberResponse_phoneNumberArn' - The Amazon Resource Name (ARN) of the phone number.
--
-- 'phoneNumberId', 'updatePhoneNumberResponse_phoneNumberId' - A unique identifier for the phone number.
--
-- 'httpStatus', 'updatePhoneNumberResponse_httpStatus' - The response's http status code.
newUpdatePhoneNumberResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdatePhoneNumberResponse
newUpdatePhoneNumberResponse :: Int -> UpdatePhoneNumberResponse
newUpdatePhoneNumberResponse Int
pHttpStatus_ =
  UpdatePhoneNumberResponse'
    { $sel:phoneNumberArn:UpdatePhoneNumberResponse' :: Maybe Text
phoneNumberArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:phoneNumberId:UpdatePhoneNumberResponse' :: Maybe Text
phoneNumberId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdatePhoneNumberResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the phone number.
updatePhoneNumberResponse_phoneNumberArn :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe Prelude.Text)
updatePhoneNumberResponse_phoneNumberArn :: Lens' UpdatePhoneNumberResponse (Maybe Text)
updatePhoneNumberResponse_phoneNumberArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe Text
phoneNumberArn :: Maybe Text
$sel:phoneNumberArn:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
phoneNumberArn} -> Maybe Text
phoneNumberArn) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe Text
a -> UpdatePhoneNumberResponse
s {$sel:phoneNumberArn:UpdatePhoneNumberResponse' :: Maybe Text
phoneNumberArn = Maybe Text
a} :: UpdatePhoneNumberResponse)

-- | A unique identifier for the phone number.
updatePhoneNumberResponse_phoneNumberId :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe Prelude.Text)
updatePhoneNumberResponse_phoneNumberId :: Lens' UpdatePhoneNumberResponse (Maybe Text)
updatePhoneNumberResponse_phoneNumberId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe Text
phoneNumberId :: Maybe Text
$sel:phoneNumberId:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
phoneNumberId} -> Maybe Text
phoneNumberId) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe Text
a -> UpdatePhoneNumberResponse
s {$sel:phoneNumberId:UpdatePhoneNumberResponse' :: Maybe Text
phoneNumberId = Maybe Text
a} :: UpdatePhoneNumberResponse)

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

instance Prelude.NFData UpdatePhoneNumberResponse where
  rnf :: UpdatePhoneNumberResponse -> ()
rnf UpdatePhoneNumberResponse' {Int
Maybe Text
httpStatus :: Int
phoneNumberId :: Maybe Text
phoneNumberArn :: Maybe Text
$sel:httpStatus:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Int
$sel:phoneNumberId:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
$sel:phoneNumberArn:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
phoneNumberArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
phoneNumberId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus