{-# 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.ClaimPhoneNumber
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Claims an available phone number to your Amazon Connect instance or
-- traffic distribution group. You can call this API only in the same
-- Amazon Web Services Region where the Amazon Connect instance or traffic
-- distribution group was created.
--
-- For more information about how to use this operation, see
-- <https://docs.aws.amazon.com/connect/latest/adminguide/claim-phone-number.html Claim a phone number in your country>
-- and
-- <https://docs.aws.amazon.com/connect/latest/adminguide/claim-phone-numbers-traffic-distribution-groups.html Claim phone numbers to traffic distribution groups>
-- in the /Amazon Connect Administrator Guide/.
--
-- You can call the
-- <https://docs.aws.amazon.com/connect/latest/APIReference/API_SearchAvailablePhoneNumbers.html SearchAvailablePhoneNumbers>
-- API for available phone numbers that you can claim. Call the
-- <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_ClaimPhoneNumber.html ClaimPhoneNumber>
-- operation.
module Amazonka.Connect.ClaimPhoneNumber
  ( -- * Creating a Request
    ClaimPhoneNumber (..),
    newClaimPhoneNumber,

    -- * Request Lenses
    claimPhoneNumber_clientToken,
    claimPhoneNumber_phoneNumberDescription,
    claimPhoneNumber_tags,
    claimPhoneNumber_targetArn,
    claimPhoneNumber_phoneNumber,

    -- * Destructuring the Response
    ClaimPhoneNumberResponse (..),
    newClaimPhoneNumberResponse,

    -- * Response Lenses
    claimPhoneNumberResponse_phoneNumberArn,
    claimPhoneNumberResponse_phoneNumberId,
    claimPhoneNumberResponse_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:/ 'newClaimPhoneNumber' smart constructor.
data ClaimPhoneNumber = ClaimPhoneNumber'
  { -- | 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>.
    --
    -- Pattern:
    -- @^[a-f0-9]{8}-[a-f0-9]{4}-[a-f0-9]{4}-[a-f0-9]{4}-[a-f0-9]{12}$@
    ClaimPhoneNumber -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The description of the phone number.
    ClaimPhoneNumber -> Maybe Text
phoneNumberDescription :: Prelude.Maybe Prelude.Text,
    -- | The tags used to organize, track, or control access for this resource.
    -- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
    ClaimPhoneNumber -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The Amazon Resource Name (ARN) for Amazon Connect instances or traffic
    -- distribution groups that phone numbers are claimed to.
    ClaimPhoneNumber -> Text
targetArn :: Prelude.Text,
    -- | The phone number you want to claim. Phone numbers are formatted
    -- @[+] [country code] [subscriber number including area code]@.
    ClaimPhoneNumber -> Text
phoneNumber :: Prelude.Text
  }
  deriving (ClaimPhoneNumber -> ClaimPhoneNumber -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClaimPhoneNumber -> ClaimPhoneNumber -> Bool
$c/= :: ClaimPhoneNumber -> ClaimPhoneNumber -> Bool
== :: ClaimPhoneNumber -> ClaimPhoneNumber -> Bool
$c== :: ClaimPhoneNumber -> ClaimPhoneNumber -> Bool
Prelude.Eq, ReadPrec [ClaimPhoneNumber]
ReadPrec ClaimPhoneNumber
Int -> ReadS ClaimPhoneNumber
ReadS [ClaimPhoneNumber]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClaimPhoneNumber]
$creadListPrec :: ReadPrec [ClaimPhoneNumber]
readPrec :: ReadPrec ClaimPhoneNumber
$creadPrec :: ReadPrec ClaimPhoneNumber
readList :: ReadS [ClaimPhoneNumber]
$creadList :: ReadS [ClaimPhoneNumber]
readsPrec :: Int -> ReadS ClaimPhoneNumber
$creadsPrec :: Int -> ReadS ClaimPhoneNumber
Prelude.Read, Int -> ClaimPhoneNumber -> ShowS
[ClaimPhoneNumber] -> ShowS
ClaimPhoneNumber -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClaimPhoneNumber] -> ShowS
$cshowList :: [ClaimPhoneNumber] -> ShowS
show :: ClaimPhoneNumber -> String
$cshow :: ClaimPhoneNumber -> String
showsPrec :: Int -> ClaimPhoneNumber -> ShowS
$cshowsPrec :: Int -> ClaimPhoneNumber -> ShowS
Prelude.Show, forall x. Rep ClaimPhoneNumber x -> ClaimPhoneNumber
forall x. ClaimPhoneNumber -> Rep ClaimPhoneNumber x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClaimPhoneNumber x -> ClaimPhoneNumber
$cfrom :: forall x. ClaimPhoneNumber -> Rep ClaimPhoneNumber x
Prelude.Generic)

-- |
-- Create a value of 'ClaimPhoneNumber' 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', 'claimPhoneNumber_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>.
--
-- Pattern:
-- @^[a-f0-9]{8}-[a-f0-9]{4}-[a-f0-9]{4}-[a-f0-9]{4}-[a-f0-9]{12}$@
--
-- 'phoneNumberDescription', 'claimPhoneNumber_phoneNumberDescription' - The description of the phone number.
--
-- 'tags', 'claimPhoneNumber_tags' - The tags used to organize, track, or control access for this resource.
-- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
--
-- 'targetArn', 'claimPhoneNumber_targetArn' - The Amazon Resource Name (ARN) for Amazon Connect instances or traffic
-- distribution groups that phone numbers are claimed to.
--
-- 'phoneNumber', 'claimPhoneNumber_phoneNumber' - The phone number you want to claim. Phone numbers are formatted
-- @[+] [country code] [subscriber number including area code]@.
newClaimPhoneNumber ::
  -- | 'targetArn'
  Prelude.Text ->
  -- | 'phoneNumber'
  Prelude.Text ->
  ClaimPhoneNumber
newClaimPhoneNumber :: Text -> Text -> ClaimPhoneNumber
newClaimPhoneNumber Text
pTargetArn_ Text
pPhoneNumber_ =
  ClaimPhoneNumber'
    { $sel:clientToken:ClaimPhoneNumber' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:phoneNumberDescription:ClaimPhoneNumber' :: Maybe Text
phoneNumberDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ClaimPhoneNumber' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:targetArn:ClaimPhoneNumber' :: Text
targetArn = Text
pTargetArn_,
      $sel:phoneNumber:ClaimPhoneNumber' :: Text
phoneNumber = Text
pPhoneNumber_
    }

-- | 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>.
--
-- Pattern:
-- @^[a-f0-9]{8}-[a-f0-9]{4}-[a-f0-9]{4}-[a-f0-9]{4}-[a-f0-9]{12}$@
claimPhoneNumber_clientToken :: Lens.Lens' ClaimPhoneNumber (Prelude.Maybe Prelude.Text)
claimPhoneNumber_clientToken :: Lens' ClaimPhoneNumber (Maybe Text)
claimPhoneNumber_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClaimPhoneNumber' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:ClaimPhoneNumber' :: ClaimPhoneNumber -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: ClaimPhoneNumber
s@ClaimPhoneNumber' {} Maybe Text
a -> ClaimPhoneNumber
s {$sel:clientToken:ClaimPhoneNumber' :: Maybe Text
clientToken = Maybe Text
a} :: ClaimPhoneNumber)

-- | The description of the phone number.
claimPhoneNumber_phoneNumberDescription :: Lens.Lens' ClaimPhoneNumber (Prelude.Maybe Prelude.Text)
claimPhoneNumber_phoneNumberDescription :: Lens' ClaimPhoneNumber (Maybe Text)
claimPhoneNumber_phoneNumberDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClaimPhoneNumber' {Maybe Text
phoneNumberDescription :: Maybe Text
$sel:phoneNumberDescription:ClaimPhoneNumber' :: ClaimPhoneNumber -> Maybe Text
phoneNumberDescription} -> Maybe Text
phoneNumberDescription) (\s :: ClaimPhoneNumber
s@ClaimPhoneNumber' {} Maybe Text
a -> ClaimPhoneNumber
s {$sel:phoneNumberDescription:ClaimPhoneNumber' :: Maybe Text
phoneNumberDescription = Maybe Text
a} :: ClaimPhoneNumber)

-- | The tags used to organize, track, or control access for this resource.
-- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
claimPhoneNumber_tags :: Lens.Lens' ClaimPhoneNumber (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
claimPhoneNumber_tags :: Lens' ClaimPhoneNumber (Maybe (HashMap Text Text))
claimPhoneNumber_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClaimPhoneNumber' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:ClaimPhoneNumber' :: ClaimPhoneNumber -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: ClaimPhoneNumber
s@ClaimPhoneNumber' {} Maybe (HashMap Text Text)
a -> ClaimPhoneNumber
s {$sel:tags:ClaimPhoneNumber' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: ClaimPhoneNumber) 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 Amazon Resource Name (ARN) for Amazon Connect instances or traffic
-- distribution groups that phone numbers are claimed to.
claimPhoneNumber_targetArn :: Lens.Lens' ClaimPhoneNumber Prelude.Text
claimPhoneNumber_targetArn :: Lens' ClaimPhoneNumber Text
claimPhoneNumber_targetArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClaimPhoneNumber' {Text
targetArn :: Text
$sel:targetArn:ClaimPhoneNumber' :: ClaimPhoneNumber -> Text
targetArn} -> Text
targetArn) (\s :: ClaimPhoneNumber
s@ClaimPhoneNumber' {} Text
a -> ClaimPhoneNumber
s {$sel:targetArn:ClaimPhoneNumber' :: Text
targetArn = Text
a} :: ClaimPhoneNumber)

-- | The phone number you want to claim. Phone numbers are formatted
-- @[+] [country code] [subscriber number including area code]@.
claimPhoneNumber_phoneNumber :: Lens.Lens' ClaimPhoneNumber Prelude.Text
claimPhoneNumber_phoneNumber :: Lens' ClaimPhoneNumber Text
claimPhoneNumber_phoneNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClaimPhoneNumber' {Text
phoneNumber :: Text
$sel:phoneNumber:ClaimPhoneNumber' :: ClaimPhoneNumber -> Text
phoneNumber} -> Text
phoneNumber) (\s :: ClaimPhoneNumber
s@ClaimPhoneNumber' {} Text
a -> ClaimPhoneNumber
s {$sel:phoneNumber:ClaimPhoneNumber' :: Text
phoneNumber = Text
a} :: ClaimPhoneNumber)

instance Core.AWSRequest ClaimPhoneNumber where
  type
    AWSResponse ClaimPhoneNumber =
      ClaimPhoneNumberResponse
  request :: (Service -> Service)
-> ClaimPhoneNumber -> Request ClaimPhoneNumber
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 ClaimPhoneNumber
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ClaimPhoneNumber)))
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 -> ClaimPhoneNumberResponse
ClaimPhoneNumberResponse'
            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 ClaimPhoneNumber where
  hashWithSalt :: Int -> ClaimPhoneNumber -> Int
hashWithSalt Int
_salt ClaimPhoneNumber' {Maybe Text
Maybe (HashMap Text Text)
Text
phoneNumber :: Text
targetArn :: Text
tags :: Maybe (HashMap Text Text)
phoneNumberDescription :: Maybe Text
clientToken :: Maybe Text
$sel:phoneNumber:ClaimPhoneNumber' :: ClaimPhoneNumber -> Text
$sel:targetArn:ClaimPhoneNumber' :: ClaimPhoneNumber -> Text
$sel:tags:ClaimPhoneNumber' :: ClaimPhoneNumber -> Maybe (HashMap Text Text)
$sel:phoneNumberDescription:ClaimPhoneNumber' :: ClaimPhoneNumber -> Maybe Text
$sel:clientToken:ClaimPhoneNumber' :: ClaimPhoneNumber -> 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` Maybe Text
phoneNumberDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
targetArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
phoneNumber

instance Prelude.NFData ClaimPhoneNumber where
  rnf :: ClaimPhoneNumber -> ()
rnf ClaimPhoneNumber' {Maybe Text
Maybe (HashMap Text Text)
Text
phoneNumber :: Text
targetArn :: Text
tags :: Maybe (HashMap Text Text)
phoneNumberDescription :: Maybe Text
clientToken :: Maybe Text
$sel:phoneNumber:ClaimPhoneNumber' :: ClaimPhoneNumber -> Text
$sel:targetArn:ClaimPhoneNumber' :: ClaimPhoneNumber -> Text
$sel:tags:ClaimPhoneNumber' :: ClaimPhoneNumber -> Maybe (HashMap Text Text)
$sel:phoneNumberDescription:ClaimPhoneNumber' :: ClaimPhoneNumber -> Maybe Text
$sel:clientToken:ClaimPhoneNumber' :: ClaimPhoneNumber -> 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 Maybe Text
phoneNumberDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
targetArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
phoneNumber

instance Data.ToHeaders ClaimPhoneNumber where
  toHeaders :: ClaimPhoneNumber -> 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 ClaimPhoneNumber where
  toJSON :: ClaimPhoneNumber -> Value
toJSON ClaimPhoneNumber' {Maybe Text
Maybe (HashMap Text Text)
Text
phoneNumber :: Text
targetArn :: Text
tags :: Maybe (HashMap Text Text)
phoneNumberDescription :: Maybe Text
clientToken :: Maybe Text
$sel:phoneNumber:ClaimPhoneNumber' :: ClaimPhoneNumber -> Text
$sel:targetArn:ClaimPhoneNumber' :: ClaimPhoneNumber -> Text
$sel:tags:ClaimPhoneNumber' :: ClaimPhoneNumber -> Maybe (HashMap Text Text)
$sel:phoneNumberDescription:ClaimPhoneNumber' :: ClaimPhoneNumber -> Maybe Text
$sel:clientToken:ClaimPhoneNumber' :: ClaimPhoneNumber -> 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,
            (Key
"PhoneNumberDescription" 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
phoneNumberDescription,
            (Key
"Tags" 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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"TargetArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
targetArn),
            forall a. a -> Maybe a
Prelude.Just (Key
"PhoneNumber" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
phoneNumber)
          ]
      )

instance Data.ToPath ClaimPhoneNumber where
  toPath :: ClaimPhoneNumber -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/phone-number/claim"

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

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

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

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

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

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

instance Prelude.NFData ClaimPhoneNumberResponse where
  rnf :: ClaimPhoneNumberResponse -> ()
rnf ClaimPhoneNumberResponse' {Int
Maybe Text
httpStatus :: Int
phoneNumberId :: Maybe Text
phoneNumberArn :: Maybe Text
$sel:httpStatus:ClaimPhoneNumberResponse' :: ClaimPhoneNumberResponse -> Int
$sel:phoneNumberId:ClaimPhoneNumberResponse' :: ClaimPhoneNumberResponse -> Maybe Text
$sel:phoneNumberArn:ClaimPhoneNumberResponse' :: ClaimPhoneNumberResponse -> 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