{-# 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.Chime.ValidateE911Address
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Validates an address to be used for 911 calls made with Amazon Chime
-- Voice Connectors. You can use validated addresses in a Presence
-- Information Data Format Location Object file that you include in SIP
-- requests. That helps ensure that addresses are routed to the appropriate
-- Public Safety Answering Point.
module Amazonka.Chime.ValidateE911Address
  ( -- * Creating a Request
    ValidateE911Address (..),
    newValidateE911Address,

    -- * Request Lenses
    validateE911Address_awsAccountId,
    validateE911Address_streetNumber,
    validateE911Address_streetInfo,
    validateE911Address_city,
    validateE911Address_state,
    validateE911Address_country,
    validateE911Address_postalCode,

    -- * Destructuring the Response
    ValidateE911AddressResponse (..),
    newValidateE911AddressResponse,

    -- * Response Lenses
    validateE911AddressResponse_address,
    validateE911AddressResponse_addressExternalId,
    validateE911AddressResponse_candidateAddressList,
    validateE911AddressResponse_validationResult,
    validateE911AddressResponse_httpStatus,
  )
where

import Amazonka.Chime.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:/ 'newValidateE911Address' smart constructor.
data ValidateE911Address = ValidateE911Address'
  { -- | The AWS account ID.
    ValidateE911Address -> Text
awsAccountId :: Prelude.Text,
    -- | The address street number, such as @200@ or @2121@.
    ValidateE911Address -> Sensitive Text
streetNumber :: Data.Sensitive Prelude.Text,
    -- | The address street information, such as @8th Avenue@.
    ValidateE911Address -> Sensitive Text
streetInfo :: Data.Sensitive Prelude.Text,
    -- | The address city, such as @Portland@.
    ValidateE911Address -> Sensitive Text
city :: Data.Sensitive Prelude.Text,
    -- | The address state, such as @ME@.
    ValidateE911Address -> Sensitive Text
state :: Data.Sensitive Prelude.Text,
    -- | The address country, such as @US@.
    ValidateE911Address -> Sensitive Text
country :: Data.Sensitive Prelude.Text,
    -- | The address postal code, such as @04352@.
    ValidateE911Address -> Sensitive Text
postalCode :: Data.Sensitive Prelude.Text
  }
  deriving (ValidateE911Address -> ValidateE911Address -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValidateE911Address -> ValidateE911Address -> Bool
$c/= :: ValidateE911Address -> ValidateE911Address -> Bool
== :: ValidateE911Address -> ValidateE911Address -> Bool
$c== :: ValidateE911Address -> ValidateE911Address -> Bool
Prelude.Eq, Int -> ValidateE911Address -> ShowS
[ValidateE911Address] -> ShowS
ValidateE911Address -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ValidateE911Address] -> ShowS
$cshowList :: [ValidateE911Address] -> ShowS
show :: ValidateE911Address -> String
$cshow :: ValidateE911Address -> String
showsPrec :: Int -> ValidateE911Address -> ShowS
$cshowsPrec :: Int -> ValidateE911Address -> ShowS
Prelude.Show, forall x. Rep ValidateE911Address x -> ValidateE911Address
forall x. ValidateE911Address -> Rep ValidateE911Address x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ValidateE911Address x -> ValidateE911Address
$cfrom :: forall x. ValidateE911Address -> Rep ValidateE911Address x
Prelude.Generic)

-- |
-- Create a value of 'ValidateE911Address' 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:
--
-- 'awsAccountId', 'validateE911Address_awsAccountId' - The AWS account ID.
--
-- 'streetNumber', 'validateE911Address_streetNumber' - The address street number, such as @200@ or @2121@.
--
-- 'streetInfo', 'validateE911Address_streetInfo' - The address street information, such as @8th Avenue@.
--
-- 'city', 'validateE911Address_city' - The address city, such as @Portland@.
--
-- 'state', 'validateE911Address_state' - The address state, such as @ME@.
--
-- 'country', 'validateE911Address_country' - The address country, such as @US@.
--
-- 'postalCode', 'validateE911Address_postalCode' - The address postal code, such as @04352@.
newValidateE911Address ::
  -- | 'awsAccountId'
  Prelude.Text ->
  -- | 'streetNumber'
  Prelude.Text ->
  -- | 'streetInfo'
  Prelude.Text ->
  -- | 'city'
  Prelude.Text ->
  -- | 'state'
  Prelude.Text ->
  -- | 'country'
  Prelude.Text ->
  -- | 'postalCode'
  Prelude.Text ->
  ValidateE911Address
newValidateE911Address :: Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> ValidateE911Address
newValidateE911Address
  Text
pAwsAccountId_
  Text
pStreetNumber_
  Text
pStreetInfo_
  Text
pCity_
  Text
pState_
  Text
pCountry_
  Text
pPostalCode_ =
    ValidateE911Address'
      { $sel:awsAccountId:ValidateE911Address' :: Text
awsAccountId = Text
pAwsAccountId_,
        $sel:streetNumber:ValidateE911Address' :: Sensitive Text
streetNumber = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pStreetNumber_,
        $sel:streetInfo:ValidateE911Address' :: Sensitive Text
streetInfo = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pStreetInfo_,
        $sel:city:ValidateE911Address' :: Sensitive Text
city = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pCity_,
        $sel:state:ValidateE911Address' :: Sensitive Text
state = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pState_,
        $sel:country:ValidateE911Address' :: Sensitive Text
country = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pCountry_,
        $sel:postalCode:ValidateE911Address' :: Sensitive Text
postalCode = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pPostalCode_
      }

-- | The AWS account ID.
validateE911Address_awsAccountId :: Lens.Lens' ValidateE911Address Prelude.Text
validateE911Address_awsAccountId :: Lens' ValidateE911Address Text
validateE911Address_awsAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidateE911Address' {Text
awsAccountId :: Text
$sel:awsAccountId:ValidateE911Address' :: ValidateE911Address -> Text
awsAccountId} -> Text
awsAccountId) (\s :: ValidateE911Address
s@ValidateE911Address' {} Text
a -> ValidateE911Address
s {$sel:awsAccountId:ValidateE911Address' :: Text
awsAccountId = Text
a} :: ValidateE911Address)

-- | The address street number, such as @200@ or @2121@.
validateE911Address_streetNumber :: Lens.Lens' ValidateE911Address Prelude.Text
validateE911Address_streetNumber :: Lens' ValidateE911Address Text
validateE911Address_streetNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidateE911Address' {Sensitive Text
streetNumber :: Sensitive Text
$sel:streetNumber:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
streetNumber} -> Sensitive Text
streetNumber) (\s :: ValidateE911Address
s@ValidateE911Address' {} Sensitive Text
a -> ValidateE911Address
s {$sel:streetNumber:ValidateE911Address' :: Sensitive Text
streetNumber = Sensitive Text
a} :: ValidateE911Address) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The address street information, such as @8th Avenue@.
validateE911Address_streetInfo :: Lens.Lens' ValidateE911Address Prelude.Text
validateE911Address_streetInfo :: Lens' ValidateE911Address Text
validateE911Address_streetInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidateE911Address' {Sensitive Text
streetInfo :: Sensitive Text
$sel:streetInfo:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
streetInfo} -> Sensitive Text
streetInfo) (\s :: ValidateE911Address
s@ValidateE911Address' {} Sensitive Text
a -> ValidateE911Address
s {$sel:streetInfo:ValidateE911Address' :: Sensitive Text
streetInfo = Sensitive Text
a} :: ValidateE911Address) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The address city, such as @Portland@.
validateE911Address_city :: Lens.Lens' ValidateE911Address Prelude.Text
validateE911Address_city :: Lens' ValidateE911Address Text
validateE911Address_city = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidateE911Address' {Sensitive Text
city :: Sensitive Text
$sel:city:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
city} -> Sensitive Text
city) (\s :: ValidateE911Address
s@ValidateE911Address' {} Sensitive Text
a -> ValidateE911Address
s {$sel:city:ValidateE911Address' :: Sensitive Text
city = Sensitive Text
a} :: ValidateE911Address) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The address state, such as @ME@.
validateE911Address_state :: Lens.Lens' ValidateE911Address Prelude.Text
validateE911Address_state :: Lens' ValidateE911Address Text
validateE911Address_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidateE911Address' {Sensitive Text
state :: Sensitive Text
$sel:state:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
state} -> Sensitive Text
state) (\s :: ValidateE911Address
s@ValidateE911Address' {} Sensitive Text
a -> ValidateE911Address
s {$sel:state:ValidateE911Address' :: Sensitive Text
state = Sensitive Text
a} :: ValidateE911Address) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The address country, such as @US@.
validateE911Address_country :: Lens.Lens' ValidateE911Address Prelude.Text
validateE911Address_country :: Lens' ValidateE911Address Text
validateE911Address_country = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidateE911Address' {Sensitive Text
country :: Sensitive Text
$sel:country:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
country} -> Sensitive Text
country) (\s :: ValidateE911Address
s@ValidateE911Address' {} Sensitive Text
a -> ValidateE911Address
s {$sel:country:ValidateE911Address' :: Sensitive Text
country = Sensitive Text
a} :: ValidateE911Address) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The address postal code, such as @04352@.
validateE911Address_postalCode :: Lens.Lens' ValidateE911Address Prelude.Text
validateE911Address_postalCode :: Lens' ValidateE911Address Text
validateE911Address_postalCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidateE911Address' {Sensitive Text
postalCode :: Sensitive Text
$sel:postalCode:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
postalCode} -> Sensitive Text
postalCode) (\s :: ValidateE911Address
s@ValidateE911Address' {} Sensitive Text
a -> ValidateE911Address
s {$sel:postalCode:ValidateE911Address' :: Sensitive Text
postalCode = Sensitive Text
a} :: ValidateE911Address) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

instance Core.AWSRequest ValidateE911Address where
  type
    AWSResponse ValidateE911Address =
      ValidateE911AddressResponse
  request :: (Service -> Service)
-> ValidateE911Address -> Request ValidateE911Address
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 ValidateE911Address
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ValidateE911Address)))
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 Address
-> Maybe Text
-> Maybe [CandidateAddress]
-> Maybe Natural
-> Int
-> ValidateE911AddressResponse
ValidateE911AddressResponse'
            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
"Address")
            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
"AddressExternalId")
            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
"CandidateAddressList"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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
"ValidationResult")
            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 ValidateE911Address where
  hashWithSalt :: Int -> ValidateE911Address -> Int
hashWithSalt Int
_salt ValidateE911Address' {Text
Sensitive Text
postalCode :: Sensitive Text
country :: Sensitive Text
state :: Sensitive Text
city :: Sensitive Text
streetInfo :: Sensitive Text
streetNumber :: Sensitive Text
awsAccountId :: Text
$sel:postalCode:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:country:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:state:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:city:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:streetInfo:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:streetNumber:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:awsAccountId:ValidateE911Address' :: ValidateE911Address -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
awsAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
streetNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
streetInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
city
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
country
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
postalCode

instance Prelude.NFData ValidateE911Address where
  rnf :: ValidateE911Address -> ()
rnf ValidateE911Address' {Text
Sensitive Text
postalCode :: Sensitive Text
country :: Sensitive Text
state :: Sensitive Text
city :: Sensitive Text
streetInfo :: Sensitive Text
streetNumber :: Sensitive Text
awsAccountId :: Text
$sel:postalCode:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:country:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:state:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:city:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:streetInfo:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:streetNumber:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:awsAccountId:ValidateE911Address' :: ValidateE911Address -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
awsAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
streetNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
streetInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
city
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
country
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
postalCode

instance Data.ToHeaders ValidateE911Address where
  toHeaders :: ValidateE911Address -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON ValidateE911Address where
  toJSON :: ValidateE911Address -> Value
toJSON ValidateE911Address' {Text
Sensitive Text
postalCode :: Sensitive Text
country :: Sensitive Text
state :: Sensitive Text
city :: Sensitive Text
streetInfo :: Sensitive Text
streetNumber :: Sensitive Text
awsAccountId :: Text
$sel:postalCode:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:country:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:state:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:city:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:streetInfo:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:streetNumber:ValidateE911Address' :: ValidateE911Address -> Sensitive Text
$sel:awsAccountId:ValidateE911Address' :: ValidateE911Address -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"AwsAccountId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
awsAccountId),
            forall a. a -> Maybe a
Prelude.Just (Key
"StreetNumber" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
streetNumber),
            forall a. a -> Maybe a
Prelude.Just (Key
"StreetInfo" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
streetInfo),
            forall a. a -> Maybe a
Prelude.Just (Key
"City" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
city),
            forall a. a -> Maybe a
Prelude.Just (Key
"State" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
state),
            forall a. a -> Maybe a
Prelude.Just (Key
"Country" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
country),
            forall a. a -> Maybe a
Prelude.Just (Key
"PostalCode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
postalCode)
          ]
      )

instance Data.ToPath ValidateE911Address where
  toPath :: ValidateE911Address -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/emergency-calling/address"

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

-- | /See:/ 'newValidateE911AddressResponse' smart constructor.
data ValidateE911AddressResponse = ValidateE911AddressResponse'
  { -- | The validated address.
    ValidateE911AddressResponse -> Maybe Address
address :: Prelude.Maybe Address,
    -- | The ID that represents the address.
    ValidateE911AddressResponse -> Maybe Text
addressExternalId :: Prelude.Maybe Prelude.Text,
    -- | The list of address suggestions.
    ValidateE911AddressResponse -> Maybe [CandidateAddress]
candidateAddressList :: Prelude.Maybe [CandidateAddress],
    -- | Number indicating the result of address validation. @0@ means the
    -- address was perfect as is and successfully validated. @1@ means the
    -- address was corrected. @2@ means the address sent was not close enough
    -- and was not validated.
    ValidateE911AddressResponse -> Maybe Natural
validationResult :: Prelude.Maybe Prelude.Natural,
    -- | The response's http status code.
    ValidateE911AddressResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ValidateE911AddressResponse -> ValidateE911AddressResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValidateE911AddressResponse -> ValidateE911AddressResponse -> Bool
$c/= :: ValidateE911AddressResponse -> ValidateE911AddressResponse -> Bool
== :: ValidateE911AddressResponse -> ValidateE911AddressResponse -> Bool
$c== :: ValidateE911AddressResponse -> ValidateE911AddressResponse -> Bool
Prelude.Eq, Int -> ValidateE911AddressResponse -> ShowS
[ValidateE911AddressResponse] -> ShowS
ValidateE911AddressResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ValidateE911AddressResponse] -> ShowS
$cshowList :: [ValidateE911AddressResponse] -> ShowS
show :: ValidateE911AddressResponse -> String
$cshow :: ValidateE911AddressResponse -> String
showsPrec :: Int -> ValidateE911AddressResponse -> ShowS
$cshowsPrec :: Int -> ValidateE911AddressResponse -> ShowS
Prelude.Show, forall x.
Rep ValidateE911AddressResponse x -> ValidateE911AddressResponse
forall x.
ValidateE911AddressResponse -> Rep ValidateE911AddressResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ValidateE911AddressResponse x -> ValidateE911AddressResponse
$cfrom :: forall x.
ValidateE911AddressResponse -> Rep ValidateE911AddressResponse x
Prelude.Generic)

-- |
-- Create a value of 'ValidateE911AddressResponse' 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:
--
-- 'address', 'validateE911AddressResponse_address' - The validated address.
--
-- 'addressExternalId', 'validateE911AddressResponse_addressExternalId' - The ID that represents the address.
--
-- 'candidateAddressList', 'validateE911AddressResponse_candidateAddressList' - The list of address suggestions.
--
-- 'validationResult', 'validateE911AddressResponse_validationResult' - Number indicating the result of address validation. @0@ means the
-- address was perfect as is and successfully validated. @1@ means the
-- address was corrected. @2@ means the address sent was not close enough
-- and was not validated.
--
-- 'httpStatus', 'validateE911AddressResponse_httpStatus' - The response's http status code.
newValidateE911AddressResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ValidateE911AddressResponse
newValidateE911AddressResponse :: Int -> ValidateE911AddressResponse
newValidateE911AddressResponse Int
pHttpStatus_ =
  ValidateE911AddressResponse'
    { $sel:address:ValidateE911AddressResponse' :: Maybe Address
address =
        forall a. Maybe a
Prelude.Nothing,
      $sel:addressExternalId:ValidateE911AddressResponse' :: Maybe Text
addressExternalId = forall a. Maybe a
Prelude.Nothing,
      $sel:candidateAddressList:ValidateE911AddressResponse' :: Maybe [CandidateAddress]
candidateAddressList = forall a. Maybe a
Prelude.Nothing,
      $sel:validationResult:ValidateE911AddressResponse' :: Maybe Natural
validationResult = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ValidateE911AddressResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The validated address.
validateE911AddressResponse_address :: Lens.Lens' ValidateE911AddressResponse (Prelude.Maybe Address)
validateE911AddressResponse_address :: Lens' ValidateE911AddressResponse (Maybe Address)
validateE911AddressResponse_address = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidateE911AddressResponse' {Maybe Address
address :: Maybe Address
$sel:address:ValidateE911AddressResponse' :: ValidateE911AddressResponse -> Maybe Address
address} -> Maybe Address
address) (\s :: ValidateE911AddressResponse
s@ValidateE911AddressResponse' {} Maybe Address
a -> ValidateE911AddressResponse
s {$sel:address:ValidateE911AddressResponse' :: Maybe Address
address = Maybe Address
a} :: ValidateE911AddressResponse)

-- | The ID that represents the address.
validateE911AddressResponse_addressExternalId :: Lens.Lens' ValidateE911AddressResponse (Prelude.Maybe Prelude.Text)
validateE911AddressResponse_addressExternalId :: Lens' ValidateE911AddressResponse (Maybe Text)
validateE911AddressResponse_addressExternalId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidateE911AddressResponse' {Maybe Text
addressExternalId :: Maybe Text
$sel:addressExternalId:ValidateE911AddressResponse' :: ValidateE911AddressResponse -> Maybe Text
addressExternalId} -> Maybe Text
addressExternalId) (\s :: ValidateE911AddressResponse
s@ValidateE911AddressResponse' {} Maybe Text
a -> ValidateE911AddressResponse
s {$sel:addressExternalId:ValidateE911AddressResponse' :: Maybe Text
addressExternalId = Maybe Text
a} :: ValidateE911AddressResponse)

-- | The list of address suggestions.
validateE911AddressResponse_candidateAddressList :: Lens.Lens' ValidateE911AddressResponse (Prelude.Maybe [CandidateAddress])
validateE911AddressResponse_candidateAddressList :: Lens' ValidateE911AddressResponse (Maybe [CandidateAddress])
validateE911AddressResponse_candidateAddressList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidateE911AddressResponse' {Maybe [CandidateAddress]
candidateAddressList :: Maybe [CandidateAddress]
$sel:candidateAddressList:ValidateE911AddressResponse' :: ValidateE911AddressResponse -> Maybe [CandidateAddress]
candidateAddressList} -> Maybe [CandidateAddress]
candidateAddressList) (\s :: ValidateE911AddressResponse
s@ValidateE911AddressResponse' {} Maybe [CandidateAddress]
a -> ValidateE911AddressResponse
s {$sel:candidateAddressList:ValidateE911AddressResponse' :: Maybe [CandidateAddress]
candidateAddressList = Maybe [CandidateAddress]
a} :: ValidateE911AddressResponse) 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

-- | Number indicating the result of address validation. @0@ means the
-- address was perfect as is and successfully validated. @1@ means the
-- address was corrected. @2@ means the address sent was not close enough
-- and was not validated.
validateE911AddressResponse_validationResult :: Lens.Lens' ValidateE911AddressResponse (Prelude.Maybe Prelude.Natural)
validateE911AddressResponse_validationResult :: Lens' ValidateE911AddressResponse (Maybe Natural)
validateE911AddressResponse_validationResult = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ValidateE911AddressResponse' {Maybe Natural
validationResult :: Maybe Natural
$sel:validationResult:ValidateE911AddressResponse' :: ValidateE911AddressResponse -> Maybe Natural
validationResult} -> Maybe Natural
validationResult) (\s :: ValidateE911AddressResponse
s@ValidateE911AddressResponse' {} Maybe Natural
a -> ValidateE911AddressResponse
s {$sel:validationResult:ValidateE911AddressResponse' :: Maybe Natural
validationResult = Maybe Natural
a} :: ValidateE911AddressResponse)

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

instance Prelude.NFData ValidateE911AddressResponse where
  rnf :: ValidateE911AddressResponse -> ()
rnf ValidateE911AddressResponse' {Int
Maybe Natural
Maybe [CandidateAddress]
Maybe Text
Maybe Address
httpStatus :: Int
validationResult :: Maybe Natural
candidateAddressList :: Maybe [CandidateAddress]
addressExternalId :: Maybe Text
address :: Maybe Address
$sel:httpStatus:ValidateE911AddressResponse' :: ValidateE911AddressResponse -> Int
$sel:validationResult:ValidateE911AddressResponse' :: ValidateE911AddressResponse -> Maybe Natural
$sel:candidateAddressList:ValidateE911AddressResponse' :: ValidateE911AddressResponse -> Maybe [CandidateAddress]
$sel:addressExternalId:ValidateE911AddressResponse' :: ValidateE911AddressResponse -> Maybe Text
$sel:address:ValidateE911AddressResponse' :: ValidateE911AddressResponse -> Maybe Address
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Address
address
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
addressExternalId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [CandidateAddress]
candidateAddressList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
validationResult
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus