{-# 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.PinpointSmsVoiceV2.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 the configuration of an existing origination phone number. You
-- can update the opt-out list, enable or disable two-way messaging, change
-- the TwoWayChannelArn, enable or disable self-managed opt-outs, and
-- enable or disable deletion protection.
--
-- If the origination phone number is associated with a pool, an Error is
-- returned.
module Amazonka.PinpointSmsVoiceV2.UpdatePhoneNumber
  ( -- * Creating a Request
    UpdatePhoneNumber (..),
    newUpdatePhoneNumber,

    -- * Request Lenses
    updatePhoneNumber_deletionProtectionEnabled,
    updatePhoneNumber_optOutListName,
    updatePhoneNumber_selfManagedOptOutsEnabled,
    updatePhoneNumber_twoWayChannelArn,
    updatePhoneNumber_twoWayEnabled,
    updatePhoneNumber_phoneNumberId,

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

    -- * Response Lenses
    updatePhoneNumberResponse_createdTimestamp,
    updatePhoneNumberResponse_deletionProtectionEnabled,
    updatePhoneNumberResponse_isoCountryCode,
    updatePhoneNumberResponse_messageType,
    updatePhoneNumberResponse_monthlyLeasingPrice,
    updatePhoneNumberResponse_numberCapabilities,
    updatePhoneNumberResponse_numberType,
    updatePhoneNumberResponse_optOutListName,
    updatePhoneNumberResponse_phoneNumber,
    updatePhoneNumberResponse_phoneNumberArn,
    updatePhoneNumberResponse_phoneNumberId,
    updatePhoneNumberResponse_selfManagedOptOutsEnabled,
    updatePhoneNumberResponse_status,
    updatePhoneNumberResponse_twoWayChannelArn,
    updatePhoneNumberResponse_twoWayEnabled,
    updatePhoneNumberResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.PinpointSmsVoiceV2.Types
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'
  { -- | By default this is set to false. When set to true the phone number
    -- can\'t be deleted.
    UpdatePhoneNumber -> Maybe Bool
deletionProtectionEnabled :: Prelude.Maybe Prelude.Bool,
    -- | The OptOutList to add the phone number to. Valid values for this field
    -- can be either the OutOutListName or OutOutListArn.
    UpdatePhoneNumber -> Maybe Text
optOutListName :: Prelude.Maybe Prelude.Text,
    -- | By default this is set to false. When an end recipient sends a message
    -- that begins with HELP or STOP to one of your dedicated numbers, Amazon
    -- Pinpoint automatically replies with a customizable message and adds the
    -- end recipient to the OptOutList. When set to true you\'re responsible
    -- for responding to HELP and STOP requests. You\'re also responsible for
    -- tracking and honoring opt-out requests.
    UpdatePhoneNumber -> Maybe Bool
selfManagedOptOutsEnabled :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon Resource Name (ARN) of the two way channel.
    UpdatePhoneNumber -> Maybe Text
twoWayChannelArn :: Prelude.Maybe Prelude.Text,
    -- | By default this is set to false. When set to true you can receive
    -- incoming text messages from your end recipients.
    UpdatePhoneNumber -> Maybe Bool
twoWayEnabled :: Prelude.Maybe Prelude.Bool,
    -- | The unique identifier of the phone number. Valid values for this field
    -- can be either the PhoneNumberId or PhoneNumberArn.
    UpdatePhoneNumber -> Text
phoneNumberId :: 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:
--
-- 'deletionProtectionEnabled', 'updatePhoneNumber_deletionProtectionEnabled' - By default this is set to false. When set to true the phone number
-- can\'t be deleted.
--
-- 'optOutListName', 'updatePhoneNumber_optOutListName' - The OptOutList to add the phone number to. Valid values for this field
-- can be either the OutOutListName or OutOutListArn.
--
-- 'selfManagedOptOutsEnabled', 'updatePhoneNumber_selfManagedOptOutsEnabled' - By default this is set to false. When an end recipient sends a message
-- that begins with HELP or STOP to one of your dedicated numbers, Amazon
-- Pinpoint automatically replies with a customizable message and adds the
-- end recipient to the OptOutList. When set to true you\'re responsible
-- for responding to HELP and STOP requests. You\'re also responsible for
-- tracking and honoring opt-out requests.
--
-- 'twoWayChannelArn', 'updatePhoneNumber_twoWayChannelArn' - The Amazon Resource Name (ARN) of the two way channel.
--
-- 'twoWayEnabled', 'updatePhoneNumber_twoWayEnabled' - By default this is set to false. When set to true you can receive
-- incoming text messages from your end recipients.
--
-- 'phoneNumberId', 'updatePhoneNumber_phoneNumberId' - The unique identifier of the phone number. Valid values for this field
-- can be either the PhoneNumberId or PhoneNumberArn.
newUpdatePhoneNumber ::
  -- | 'phoneNumberId'
  Prelude.Text ->
  UpdatePhoneNumber
newUpdatePhoneNumber :: Text -> UpdatePhoneNumber
newUpdatePhoneNumber Text
pPhoneNumberId_ =
  UpdatePhoneNumber'
    { $sel:deletionProtectionEnabled:UpdatePhoneNumber' :: Maybe Bool
deletionProtectionEnabled =
        forall a. Maybe a
Prelude.Nothing,
      $sel:optOutListName:UpdatePhoneNumber' :: Maybe Text
optOutListName = forall a. Maybe a
Prelude.Nothing,
      $sel:selfManagedOptOutsEnabled:UpdatePhoneNumber' :: Maybe Bool
selfManagedOptOutsEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:twoWayChannelArn:UpdatePhoneNumber' :: Maybe Text
twoWayChannelArn = forall a. Maybe a
Prelude.Nothing,
      $sel:twoWayEnabled:UpdatePhoneNumber' :: Maybe Bool
twoWayEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:phoneNumberId:UpdatePhoneNumber' :: Text
phoneNumberId = Text
pPhoneNumberId_
    }

-- | By default this is set to false. When set to true the phone number
-- can\'t be deleted.
updatePhoneNumber_deletionProtectionEnabled :: Lens.Lens' UpdatePhoneNumber (Prelude.Maybe Prelude.Bool)
updatePhoneNumber_deletionProtectionEnabled :: Lens' UpdatePhoneNumber (Maybe Bool)
updatePhoneNumber_deletionProtectionEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumber' {Maybe Bool
deletionProtectionEnabled :: Maybe Bool
$sel:deletionProtectionEnabled:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Bool
deletionProtectionEnabled} -> Maybe Bool
deletionProtectionEnabled) (\s :: UpdatePhoneNumber
s@UpdatePhoneNumber' {} Maybe Bool
a -> UpdatePhoneNumber
s {$sel:deletionProtectionEnabled:UpdatePhoneNumber' :: Maybe Bool
deletionProtectionEnabled = Maybe Bool
a} :: UpdatePhoneNumber)

-- | The OptOutList to add the phone number to. Valid values for this field
-- can be either the OutOutListName or OutOutListArn.
updatePhoneNumber_optOutListName :: Lens.Lens' UpdatePhoneNumber (Prelude.Maybe Prelude.Text)
updatePhoneNumber_optOutListName :: Lens' UpdatePhoneNumber (Maybe Text)
updatePhoneNumber_optOutListName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumber' {Maybe Text
optOutListName :: Maybe Text
$sel:optOutListName:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
optOutListName} -> Maybe Text
optOutListName) (\s :: UpdatePhoneNumber
s@UpdatePhoneNumber' {} Maybe Text
a -> UpdatePhoneNumber
s {$sel:optOutListName:UpdatePhoneNumber' :: Maybe Text
optOutListName = Maybe Text
a} :: UpdatePhoneNumber)

-- | By default this is set to false. When an end recipient sends a message
-- that begins with HELP or STOP to one of your dedicated numbers, Amazon
-- Pinpoint automatically replies with a customizable message and adds the
-- end recipient to the OptOutList. When set to true you\'re responsible
-- for responding to HELP and STOP requests. You\'re also responsible for
-- tracking and honoring opt-out requests.
updatePhoneNumber_selfManagedOptOutsEnabled :: Lens.Lens' UpdatePhoneNumber (Prelude.Maybe Prelude.Bool)
updatePhoneNumber_selfManagedOptOutsEnabled :: Lens' UpdatePhoneNumber (Maybe Bool)
updatePhoneNumber_selfManagedOptOutsEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumber' {Maybe Bool
selfManagedOptOutsEnabled :: Maybe Bool
$sel:selfManagedOptOutsEnabled:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Bool
selfManagedOptOutsEnabled} -> Maybe Bool
selfManagedOptOutsEnabled) (\s :: UpdatePhoneNumber
s@UpdatePhoneNumber' {} Maybe Bool
a -> UpdatePhoneNumber
s {$sel:selfManagedOptOutsEnabled:UpdatePhoneNumber' :: Maybe Bool
selfManagedOptOutsEnabled = Maybe Bool
a} :: UpdatePhoneNumber)

-- | The Amazon Resource Name (ARN) of the two way channel.
updatePhoneNumber_twoWayChannelArn :: Lens.Lens' UpdatePhoneNumber (Prelude.Maybe Prelude.Text)
updatePhoneNumber_twoWayChannelArn :: Lens' UpdatePhoneNumber (Maybe Text)
updatePhoneNumber_twoWayChannelArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumber' {Maybe Text
twoWayChannelArn :: Maybe Text
$sel:twoWayChannelArn:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
twoWayChannelArn} -> Maybe Text
twoWayChannelArn) (\s :: UpdatePhoneNumber
s@UpdatePhoneNumber' {} Maybe Text
a -> UpdatePhoneNumber
s {$sel:twoWayChannelArn:UpdatePhoneNumber' :: Maybe Text
twoWayChannelArn = Maybe Text
a} :: UpdatePhoneNumber)

-- | By default this is set to false. When set to true you can receive
-- incoming text messages from your end recipients.
updatePhoneNumber_twoWayEnabled :: Lens.Lens' UpdatePhoneNumber (Prelude.Maybe Prelude.Bool)
updatePhoneNumber_twoWayEnabled :: Lens' UpdatePhoneNumber (Maybe Bool)
updatePhoneNumber_twoWayEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumber' {Maybe Bool
twoWayEnabled :: Maybe Bool
$sel:twoWayEnabled:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Bool
twoWayEnabled} -> Maybe Bool
twoWayEnabled) (\s :: UpdatePhoneNumber
s@UpdatePhoneNumber' {} Maybe Bool
a -> UpdatePhoneNumber
s {$sel:twoWayEnabled:UpdatePhoneNumber' :: Maybe Bool
twoWayEnabled = Maybe Bool
a} :: UpdatePhoneNumber)

-- | The unique identifier of the phone number. Valid values for this field
-- can be either the PhoneNumberId or PhoneNumberArn.
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)

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.postJSON (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 POSIX
-> Maybe Bool
-> Maybe Text
-> Maybe MessageType
-> Maybe Text
-> Maybe (NonEmpty NumberCapability)
-> Maybe NumberType
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe NumberStatus
-> Maybe Text
-> Maybe Bool
-> 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
"CreatedTimestamp")
            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
"DeletionProtectionEnabled")
            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
"IsoCountryCode")
            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
"MessageType")
            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
"MonthlyLeasingPrice")
            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
"NumberCapabilities")
            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
"NumberType")
            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
"OptOutListName")
            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
"PhoneNumber")
            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
"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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SelfManagedOptOutsEnabled")
            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
"Status")
            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
"TwoWayChannelArn")
            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
"TwoWayEnabled")
            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 Bool
Maybe Text
Text
phoneNumberId :: Text
twoWayEnabled :: Maybe Bool
twoWayChannelArn :: Maybe Text
selfManagedOptOutsEnabled :: Maybe Bool
optOutListName :: Maybe Text
deletionProtectionEnabled :: Maybe Bool
$sel:phoneNumberId:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
$sel:twoWayEnabled:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Bool
$sel:twoWayChannelArn:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
$sel:selfManagedOptOutsEnabled:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Bool
$sel:optOutListName:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
$sel:deletionProtectionEnabled:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deletionProtectionEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
optOutListName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
selfManagedOptOutsEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
twoWayChannelArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
twoWayEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
phoneNumberId

instance Prelude.NFData UpdatePhoneNumber where
  rnf :: UpdatePhoneNumber -> ()
rnf UpdatePhoneNumber' {Maybe Bool
Maybe Text
Text
phoneNumberId :: Text
twoWayEnabled :: Maybe Bool
twoWayChannelArn :: Maybe Text
selfManagedOptOutsEnabled :: Maybe Bool
optOutListName :: Maybe Text
deletionProtectionEnabled :: Maybe Bool
$sel:phoneNumberId:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
$sel:twoWayEnabled:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Bool
$sel:twoWayChannelArn:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
$sel:selfManagedOptOutsEnabled:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Bool
$sel:optOutListName:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
$sel:deletionProtectionEnabled:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deletionProtectionEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
optOutListName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
selfManagedOptOutsEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
twoWayChannelArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
twoWayEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
phoneNumberId

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
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"PinpointSMSVoiceV2.UpdatePhoneNumber" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdatePhoneNumber where
  toJSON :: UpdatePhoneNumber -> Value
toJSON UpdatePhoneNumber' {Maybe Bool
Maybe Text
Text
phoneNumberId :: Text
twoWayEnabled :: Maybe Bool
twoWayChannelArn :: Maybe Text
selfManagedOptOutsEnabled :: Maybe Bool
optOutListName :: Maybe Text
deletionProtectionEnabled :: Maybe Bool
$sel:phoneNumberId:UpdatePhoneNumber' :: UpdatePhoneNumber -> Text
$sel:twoWayEnabled:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Bool
$sel:twoWayChannelArn:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
$sel:selfManagedOptOutsEnabled:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Bool
$sel:optOutListName:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Text
$sel:deletionProtectionEnabled:UpdatePhoneNumber' :: UpdatePhoneNumber -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DeletionProtectionEnabled" 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 Bool
deletionProtectionEnabled,
            (Key
"OptOutListName" 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
optOutListName,
            (Key
"SelfManagedOptOutsEnabled" 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 Bool
selfManagedOptOutsEnabled,
            (Key
"TwoWayChannelArn" 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
twoWayChannelArn,
            (Key
"TwoWayEnabled" 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 Bool
twoWayEnabled,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"PhoneNumberId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
phoneNumberId)
          ]
      )

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

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 time when the phone number was created, in
    -- <https://www.epochconverter.com/ UNIX epoch time> format.
    UpdatePhoneNumberResponse -> Maybe POSIX
createdTimestamp :: Prelude.Maybe Data.POSIX,
    -- | When set to true the phone number can\'t be deleted.
    UpdatePhoneNumberResponse -> Maybe Bool
deletionProtectionEnabled :: Prelude.Maybe Prelude.Bool,
    -- | The two-character code, in ISO 3166-1 alpha-2 format, for the country or
    -- region.
    UpdatePhoneNumberResponse -> Maybe Text
isoCountryCode :: Prelude.Maybe Prelude.Text,
    -- | The type of message. Valid values are TRANSACTIONAL for messages that
    -- are critical or time-sensitive and PROMOTIONAL for messages that aren\'t
    -- critical or time-sensitive.
    UpdatePhoneNumberResponse -> Maybe MessageType
messageType :: Prelude.Maybe MessageType,
    -- | The monthly leasing price of the phone number, in US dollars.
    UpdatePhoneNumberResponse -> Maybe Text
monthlyLeasingPrice :: Prelude.Maybe Prelude.Text,
    -- | Specifies if the number could be used for text messages, voice or both.
    UpdatePhoneNumberResponse -> Maybe (NonEmpty NumberCapability)
numberCapabilities :: Prelude.Maybe (Prelude.NonEmpty NumberCapability),
    -- | The type of number that was requested.
    UpdatePhoneNumberResponse -> Maybe NumberType
numberType :: Prelude.Maybe NumberType,
    -- | The name of the OptOutList associated with the phone number.
    UpdatePhoneNumberResponse -> Maybe Text
optOutListName :: Prelude.Maybe Prelude.Text,
    -- | The phone number that was updated.
    UpdatePhoneNumberResponse -> Maybe Text
phoneNumber :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the updated phone number.
    UpdatePhoneNumberResponse -> Maybe Text
phoneNumberArn :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier of the phone number.
    UpdatePhoneNumberResponse -> Maybe Text
phoneNumberId :: Prelude.Maybe Prelude.Text,
    -- | This is true if self managed opt-out are enabled.
    UpdatePhoneNumberResponse -> Maybe Bool
selfManagedOptOutsEnabled :: Prelude.Maybe Prelude.Bool,
    -- | The current status of the request.
    UpdatePhoneNumberResponse -> Maybe NumberStatus
status :: Prelude.Maybe NumberStatus,
    -- | The Amazon Resource Name (ARN) of the two way channel.
    UpdatePhoneNumberResponse -> Maybe Text
twoWayChannelArn :: Prelude.Maybe Prelude.Text,
    -- | By default this is set to false. When set to true you can receive
    -- incoming text messages from your end recipients.
    UpdatePhoneNumberResponse -> Maybe Bool
twoWayEnabled :: Prelude.Maybe Prelude.Bool,
    -- | 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:
--
-- 'createdTimestamp', 'updatePhoneNumberResponse_createdTimestamp' - The time when the phone number was created, in
-- <https://www.epochconverter.com/ UNIX epoch time> format.
--
-- 'deletionProtectionEnabled', 'updatePhoneNumberResponse_deletionProtectionEnabled' - When set to true the phone number can\'t be deleted.
--
-- 'isoCountryCode', 'updatePhoneNumberResponse_isoCountryCode' - The two-character code, in ISO 3166-1 alpha-2 format, for the country or
-- region.
--
-- 'messageType', 'updatePhoneNumberResponse_messageType' - The type of message. Valid values are TRANSACTIONAL for messages that
-- are critical or time-sensitive and PROMOTIONAL for messages that aren\'t
-- critical or time-sensitive.
--
-- 'monthlyLeasingPrice', 'updatePhoneNumberResponse_monthlyLeasingPrice' - The monthly leasing price of the phone number, in US dollars.
--
-- 'numberCapabilities', 'updatePhoneNumberResponse_numberCapabilities' - Specifies if the number could be used for text messages, voice or both.
--
-- 'numberType', 'updatePhoneNumberResponse_numberType' - The type of number that was requested.
--
-- 'optOutListName', 'updatePhoneNumberResponse_optOutListName' - The name of the OptOutList associated with the phone number.
--
-- 'phoneNumber', 'updatePhoneNumberResponse_phoneNumber' - The phone number that was updated.
--
-- 'phoneNumberArn', 'updatePhoneNumberResponse_phoneNumberArn' - The Amazon Resource Name (ARN) of the updated phone number.
--
-- 'phoneNumberId', 'updatePhoneNumberResponse_phoneNumberId' - The unique identifier of the phone number.
--
-- 'selfManagedOptOutsEnabled', 'updatePhoneNumberResponse_selfManagedOptOutsEnabled' - This is true if self managed opt-out are enabled.
--
-- 'status', 'updatePhoneNumberResponse_status' - The current status of the request.
--
-- 'twoWayChannelArn', 'updatePhoneNumberResponse_twoWayChannelArn' - The Amazon Resource Name (ARN) of the two way channel.
--
-- 'twoWayEnabled', 'updatePhoneNumberResponse_twoWayEnabled' - By default this is set to false. When set to true you can receive
-- incoming text messages from your end recipients.
--
-- 'httpStatus', 'updatePhoneNumberResponse_httpStatus' - The response's http status code.
newUpdatePhoneNumberResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdatePhoneNumberResponse
newUpdatePhoneNumberResponse :: Int -> UpdatePhoneNumberResponse
newUpdatePhoneNumberResponse Int
pHttpStatus_ =
  UpdatePhoneNumberResponse'
    { $sel:createdTimestamp:UpdatePhoneNumberResponse' :: Maybe POSIX
createdTimestamp =
        forall a. Maybe a
Prelude.Nothing,
      $sel:deletionProtectionEnabled:UpdatePhoneNumberResponse' :: Maybe Bool
deletionProtectionEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:isoCountryCode:UpdatePhoneNumberResponse' :: Maybe Text
isoCountryCode = forall a. Maybe a
Prelude.Nothing,
      $sel:messageType:UpdatePhoneNumberResponse' :: Maybe MessageType
messageType = forall a. Maybe a
Prelude.Nothing,
      $sel:monthlyLeasingPrice:UpdatePhoneNumberResponse' :: Maybe Text
monthlyLeasingPrice = forall a. Maybe a
Prelude.Nothing,
      $sel:numberCapabilities:UpdatePhoneNumberResponse' :: Maybe (NonEmpty NumberCapability)
numberCapabilities = forall a. Maybe a
Prelude.Nothing,
      $sel:numberType:UpdatePhoneNumberResponse' :: Maybe NumberType
numberType = forall a. Maybe a
Prelude.Nothing,
      $sel:optOutListName:UpdatePhoneNumberResponse' :: Maybe Text
optOutListName = forall a. Maybe a
Prelude.Nothing,
      $sel:phoneNumber:UpdatePhoneNumberResponse' :: Maybe Text
phoneNumber = forall a. Maybe a
Prelude.Nothing,
      $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:selfManagedOptOutsEnabled:UpdatePhoneNumberResponse' :: Maybe Bool
selfManagedOptOutsEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:status:UpdatePhoneNumberResponse' :: Maybe NumberStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:twoWayChannelArn:UpdatePhoneNumberResponse' :: Maybe Text
twoWayChannelArn = forall a. Maybe a
Prelude.Nothing,
      $sel:twoWayEnabled:UpdatePhoneNumberResponse' :: Maybe Bool
twoWayEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdatePhoneNumberResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The time when the phone number was created, in
-- <https://www.epochconverter.com/ UNIX epoch time> format.
updatePhoneNumberResponse_createdTimestamp :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe Prelude.UTCTime)
updatePhoneNumberResponse_createdTimestamp :: Lens' UpdatePhoneNumberResponse (Maybe UTCTime)
updatePhoneNumberResponse_createdTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe POSIX
createdTimestamp :: Maybe POSIX
$sel:createdTimestamp:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe POSIX
createdTimestamp} -> Maybe POSIX
createdTimestamp) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe POSIX
a -> UpdatePhoneNumberResponse
s {$sel:createdTimestamp:UpdatePhoneNumberResponse' :: Maybe POSIX
createdTimestamp = Maybe POSIX
a} :: UpdatePhoneNumberResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | When set to true the phone number can\'t be deleted.
updatePhoneNumberResponse_deletionProtectionEnabled :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe Prelude.Bool)
updatePhoneNumberResponse_deletionProtectionEnabled :: Lens' UpdatePhoneNumberResponse (Maybe Bool)
updatePhoneNumberResponse_deletionProtectionEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe Bool
deletionProtectionEnabled :: Maybe Bool
$sel:deletionProtectionEnabled:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Bool
deletionProtectionEnabled} -> Maybe Bool
deletionProtectionEnabled) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe Bool
a -> UpdatePhoneNumberResponse
s {$sel:deletionProtectionEnabled:UpdatePhoneNumberResponse' :: Maybe Bool
deletionProtectionEnabled = Maybe Bool
a} :: UpdatePhoneNumberResponse)

-- | The two-character code, in ISO 3166-1 alpha-2 format, for the country or
-- region.
updatePhoneNumberResponse_isoCountryCode :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe Prelude.Text)
updatePhoneNumberResponse_isoCountryCode :: Lens' UpdatePhoneNumberResponse (Maybe Text)
updatePhoneNumberResponse_isoCountryCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe Text
isoCountryCode :: Maybe Text
$sel:isoCountryCode:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
isoCountryCode} -> Maybe Text
isoCountryCode) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe Text
a -> UpdatePhoneNumberResponse
s {$sel:isoCountryCode:UpdatePhoneNumberResponse' :: Maybe Text
isoCountryCode = Maybe Text
a} :: UpdatePhoneNumberResponse)

-- | The type of message. Valid values are TRANSACTIONAL for messages that
-- are critical or time-sensitive and PROMOTIONAL for messages that aren\'t
-- critical or time-sensitive.
updatePhoneNumberResponse_messageType :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe MessageType)
updatePhoneNumberResponse_messageType :: Lens' UpdatePhoneNumberResponse (Maybe MessageType)
updatePhoneNumberResponse_messageType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe MessageType
messageType :: Maybe MessageType
$sel:messageType:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe MessageType
messageType} -> Maybe MessageType
messageType) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe MessageType
a -> UpdatePhoneNumberResponse
s {$sel:messageType:UpdatePhoneNumberResponse' :: Maybe MessageType
messageType = Maybe MessageType
a} :: UpdatePhoneNumberResponse)

-- | The monthly leasing price of the phone number, in US dollars.
updatePhoneNumberResponse_monthlyLeasingPrice :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe Prelude.Text)
updatePhoneNumberResponse_monthlyLeasingPrice :: Lens' UpdatePhoneNumberResponse (Maybe Text)
updatePhoneNumberResponse_monthlyLeasingPrice = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe Text
monthlyLeasingPrice :: Maybe Text
$sel:monthlyLeasingPrice:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
monthlyLeasingPrice} -> Maybe Text
monthlyLeasingPrice) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe Text
a -> UpdatePhoneNumberResponse
s {$sel:monthlyLeasingPrice:UpdatePhoneNumberResponse' :: Maybe Text
monthlyLeasingPrice = Maybe Text
a} :: UpdatePhoneNumberResponse)

-- | Specifies if the number could be used for text messages, voice or both.
updatePhoneNumberResponse_numberCapabilities :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe (Prelude.NonEmpty NumberCapability))
updatePhoneNumberResponse_numberCapabilities :: Lens' UpdatePhoneNumberResponse (Maybe (NonEmpty NumberCapability))
updatePhoneNumberResponse_numberCapabilities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe (NonEmpty NumberCapability)
numberCapabilities :: Maybe (NonEmpty NumberCapability)
$sel:numberCapabilities:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe (NonEmpty NumberCapability)
numberCapabilities} -> Maybe (NonEmpty NumberCapability)
numberCapabilities) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe (NonEmpty NumberCapability)
a -> UpdatePhoneNumberResponse
s {$sel:numberCapabilities:UpdatePhoneNumberResponse' :: Maybe (NonEmpty NumberCapability)
numberCapabilities = Maybe (NonEmpty NumberCapability)
a} :: UpdatePhoneNumberResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The type of number that was requested.
updatePhoneNumberResponse_numberType :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe NumberType)
updatePhoneNumberResponse_numberType :: Lens' UpdatePhoneNumberResponse (Maybe NumberType)
updatePhoneNumberResponse_numberType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe NumberType
numberType :: Maybe NumberType
$sel:numberType:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe NumberType
numberType} -> Maybe NumberType
numberType) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe NumberType
a -> UpdatePhoneNumberResponse
s {$sel:numberType:UpdatePhoneNumberResponse' :: Maybe NumberType
numberType = Maybe NumberType
a} :: UpdatePhoneNumberResponse)

-- | The name of the OptOutList associated with the phone number.
updatePhoneNumberResponse_optOutListName :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe Prelude.Text)
updatePhoneNumberResponse_optOutListName :: Lens' UpdatePhoneNumberResponse (Maybe Text)
updatePhoneNumberResponse_optOutListName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe Text
optOutListName :: Maybe Text
$sel:optOutListName:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
optOutListName} -> Maybe Text
optOutListName) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe Text
a -> UpdatePhoneNumberResponse
s {$sel:optOutListName:UpdatePhoneNumberResponse' :: Maybe Text
optOutListName = Maybe Text
a} :: UpdatePhoneNumberResponse)

-- | The phone number that was updated.
updatePhoneNumberResponse_phoneNumber :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe Prelude.Text)
updatePhoneNumberResponse_phoneNumber :: Lens' UpdatePhoneNumberResponse (Maybe Text)
updatePhoneNumberResponse_phoneNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe Text
phoneNumber :: Maybe Text
$sel:phoneNumber:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
phoneNumber} -> Maybe Text
phoneNumber) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe Text
a -> UpdatePhoneNumberResponse
s {$sel:phoneNumber:UpdatePhoneNumberResponse' :: Maybe Text
phoneNumber = Maybe Text
a} :: UpdatePhoneNumberResponse)

-- | The Amazon Resource Name (ARN) of the updated 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)

-- | The unique identifier of 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)

-- | This is true if self managed opt-out are enabled.
updatePhoneNumberResponse_selfManagedOptOutsEnabled :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe Prelude.Bool)
updatePhoneNumberResponse_selfManagedOptOutsEnabled :: Lens' UpdatePhoneNumberResponse (Maybe Bool)
updatePhoneNumberResponse_selfManagedOptOutsEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe Bool
selfManagedOptOutsEnabled :: Maybe Bool
$sel:selfManagedOptOutsEnabled:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Bool
selfManagedOptOutsEnabled} -> Maybe Bool
selfManagedOptOutsEnabled) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe Bool
a -> UpdatePhoneNumberResponse
s {$sel:selfManagedOptOutsEnabled:UpdatePhoneNumberResponse' :: Maybe Bool
selfManagedOptOutsEnabled = Maybe Bool
a} :: UpdatePhoneNumberResponse)

-- | The current status of the request.
updatePhoneNumberResponse_status :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe NumberStatus)
updatePhoneNumberResponse_status :: Lens' UpdatePhoneNumberResponse (Maybe NumberStatus)
updatePhoneNumberResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe NumberStatus
status :: Maybe NumberStatus
$sel:status:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe NumberStatus
status} -> Maybe NumberStatus
status) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe NumberStatus
a -> UpdatePhoneNumberResponse
s {$sel:status:UpdatePhoneNumberResponse' :: Maybe NumberStatus
status = Maybe NumberStatus
a} :: UpdatePhoneNumberResponse)

-- | The Amazon Resource Name (ARN) of the two way channel.
updatePhoneNumberResponse_twoWayChannelArn :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe Prelude.Text)
updatePhoneNumberResponse_twoWayChannelArn :: Lens' UpdatePhoneNumberResponse (Maybe Text)
updatePhoneNumberResponse_twoWayChannelArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe Text
twoWayChannelArn :: Maybe Text
$sel:twoWayChannelArn:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
twoWayChannelArn} -> Maybe Text
twoWayChannelArn) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe Text
a -> UpdatePhoneNumberResponse
s {$sel:twoWayChannelArn:UpdatePhoneNumberResponse' :: Maybe Text
twoWayChannelArn = Maybe Text
a} :: UpdatePhoneNumberResponse)

-- | By default this is set to false. When set to true you can receive
-- incoming text messages from your end recipients.
updatePhoneNumberResponse_twoWayEnabled :: Lens.Lens' UpdatePhoneNumberResponse (Prelude.Maybe Prelude.Bool)
updatePhoneNumberResponse_twoWayEnabled :: Lens' UpdatePhoneNumberResponse (Maybe Bool)
updatePhoneNumberResponse_twoWayEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePhoneNumberResponse' {Maybe Bool
twoWayEnabled :: Maybe Bool
$sel:twoWayEnabled:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Bool
twoWayEnabled} -> Maybe Bool
twoWayEnabled) (\s :: UpdatePhoneNumberResponse
s@UpdatePhoneNumberResponse' {} Maybe Bool
a -> UpdatePhoneNumberResponse
s {$sel:twoWayEnabled:UpdatePhoneNumberResponse' :: Maybe Bool
twoWayEnabled = Maybe Bool
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 Bool
Maybe (NonEmpty NumberCapability)
Maybe Text
Maybe POSIX
Maybe MessageType
Maybe NumberStatus
Maybe NumberType
httpStatus :: Int
twoWayEnabled :: Maybe Bool
twoWayChannelArn :: Maybe Text
status :: Maybe NumberStatus
selfManagedOptOutsEnabled :: Maybe Bool
phoneNumberId :: Maybe Text
phoneNumberArn :: Maybe Text
phoneNumber :: Maybe Text
optOutListName :: Maybe Text
numberType :: Maybe NumberType
numberCapabilities :: Maybe (NonEmpty NumberCapability)
monthlyLeasingPrice :: Maybe Text
messageType :: Maybe MessageType
isoCountryCode :: Maybe Text
deletionProtectionEnabled :: Maybe Bool
createdTimestamp :: Maybe POSIX
$sel:httpStatus:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Int
$sel:twoWayEnabled:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Bool
$sel:twoWayChannelArn:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
$sel:status:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe NumberStatus
$sel:selfManagedOptOutsEnabled:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Bool
$sel:phoneNumberId:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
$sel:phoneNumberArn:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
$sel:phoneNumber:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
$sel:optOutListName:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
$sel:numberType:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe NumberType
$sel:numberCapabilities:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe (NonEmpty NumberCapability)
$sel:monthlyLeasingPrice:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
$sel:messageType:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe MessageType
$sel:isoCountryCode:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Text
$sel:deletionProtectionEnabled:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe Bool
$sel:createdTimestamp:UpdatePhoneNumberResponse' :: UpdatePhoneNumberResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deletionProtectionEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
isoCountryCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MessageType
messageType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
monthlyLeasingPrice
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty NumberCapability)
numberCapabilities
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NumberType
numberType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
optOutListName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
phoneNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Maybe Bool
selfManagedOptOutsEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NumberStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
twoWayChannelArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
twoWayEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus