{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.CustomerProfiles.Types.Profile
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.CustomerProfiles.Types.Profile where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.CustomerProfiles.Types.Address
import Amazonka.CustomerProfiles.Types.FoundByKeyValue
import Amazonka.CustomerProfiles.Types.Gender
import Amazonka.CustomerProfiles.Types.PartyType
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | The standard profile of a customer.
--
-- /See:/ 'newProfile' smart constructor.
data Profile = Profile'
  { -- | A unique account number that you have given to the customer.
    Profile -> Maybe Text
accountNumber :: Prelude.Maybe Prelude.Text,
    -- | Any additional information relevant to the customer’s profile.
    Profile -> Maybe Text
additionalInformation :: Prelude.Maybe Prelude.Text,
    -- | A generic address associated with the customer that is not mailing,
    -- shipping, or billing.
    Profile -> Maybe Address
address :: Prelude.Maybe Address,
    -- | A key value pair of attributes of a customer profile.
    Profile -> Maybe (HashMap Text Text)
attributes :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The customer’s billing address.
    Profile -> Maybe Address
billingAddress :: Prelude.Maybe Address,
    -- | The customer’s birth date.
    Profile -> Maybe Text
birthDate :: Prelude.Maybe Prelude.Text,
    -- | The customer’s business email address.
    Profile -> Maybe Text
businessEmailAddress :: Prelude.Maybe Prelude.Text,
    -- | The name of the customer’s business.
    Profile -> Maybe Text
businessName :: Prelude.Maybe Prelude.Text,
    -- | The customer’s home phone number.
    Profile -> Maybe Text
businessPhoneNumber :: Prelude.Maybe Prelude.Text,
    -- | The customer’s email address, which has not been specified as a personal
    -- or business address.
    Profile -> Maybe Text
emailAddress :: Prelude.Maybe Prelude.Text,
    -- | The customer’s first name.
    Profile -> Maybe Text
firstName :: Prelude.Maybe Prelude.Text,
    -- | A list of items used to find a profile returned in a
    -- <https://docs.aws.amazon.com/customerprofiles/latest/APIReference/API_SearchProfiles.html SearchProfiles>
    -- response. An item is a key-value(s) pair that matches an attribute in
    -- the profile.
    --
    -- If the optional @AdditionalSearchKeys@ parameter was included in the
    -- <https://docs.aws.amazon.com/customerprofiles/latest/APIReference/API_SearchProfiles.html SearchProfiles>
    -- request, the @FoundByItems@ list should be interpreted based on the
    -- @LogicalOperator@ used in the request:
    --
    -- -   @AND@ - The profile included in the response matched all of the
    --     search keys specified in the request. The @FoundByItems@ will
    --     include all of the key-value(s) pairs that were specified in the
    --     request (as this is a requirement of @AND@ search logic).
    --
    -- -   @OR@ - The profile included in the response matched at least one of
    --     the search keys specified in the request. The @FoundByItems@ will
    --     include each of the key-value(s) pairs that the profile was found
    --     by.
    --
    -- The @OR@ relationship is the default behavior if the @LogicalOperator@
    -- parameter is not included in the
    -- <https://docs.aws.amazon.com/customerprofiles/latest/APIReference/API_SearchProfiles.html SearchProfiles>
    -- request.
    Profile -> Maybe (NonEmpty FoundByKeyValue)
foundByItems :: Prelude.Maybe (Prelude.NonEmpty FoundByKeyValue),
    -- | The gender with which the customer identifies.
    Profile -> Maybe Gender
gender :: Prelude.Maybe Gender,
    -- | The customer’s home phone number.
    Profile -> Maybe Text
homePhoneNumber :: Prelude.Maybe Prelude.Text,
    -- | The customer’s last name.
    Profile -> Maybe Text
lastName :: Prelude.Maybe Prelude.Text,
    -- | The customer’s mailing address.
    Profile -> Maybe Address
mailingAddress :: Prelude.Maybe Address,
    -- | The customer’s middle name.
    Profile -> Maybe Text
middleName :: Prelude.Maybe Prelude.Text,
    -- | The customer’s mobile phone number.
    Profile -> Maybe Text
mobilePhoneNumber :: Prelude.Maybe Prelude.Text,
    -- | The type of profile used to describe the customer.
    Profile -> Maybe PartyType
partyType :: Prelude.Maybe PartyType,
    -- | The customer’s personal email address.
    Profile -> Maybe Text
personalEmailAddress :: Prelude.Maybe Prelude.Text,
    -- | The customer\'s phone number, which has not been specified as a mobile,
    -- home, or business number.
    Profile -> Maybe Text
phoneNumber :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier of a customer profile.
    Profile -> Maybe Text
profileId :: Prelude.Maybe Prelude.Text,
    -- | The customer’s shipping address.
    Profile -> Maybe Address
shippingAddress :: Prelude.Maybe Address
  }
  deriving (Profile -> Profile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Profile -> Profile -> Bool
$c/= :: Profile -> Profile -> Bool
== :: Profile -> Profile -> Bool
$c== :: Profile -> Profile -> Bool
Prelude.Eq, ReadPrec [Profile]
ReadPrec Profile
Int -> ReadS Profile
ReadS [Profile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Profile]
$creadListPrec :: ReadPrec [Profile]
readPrec :: ReadPrec Profile
$creadPrec :: ReadPrec Profile
readList :: ReadS [Profile]
$creadList :: ReadS [Profile]
readsPrec :: Int -> ReadS Profile
$creadsPrec :: Int -> ReadS Profile
Prelude.Read, Int -> Profile -> ShowS
[Profile] -> ShowS
Profile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Profile] -> ShowS
$cshowList :: [Profile] -> ShowS
show :: Profile -> String
$cshow :: Profile -> String
showsPrec :: Int -> Profile -> ShowS
$cshowsPrec :: Int -> Profile -> ShowS
Prelude.Show, forall x. Rep Profile x -> Profile
forall x. Profile -> Rep Profile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Profile x -> Profile
$cfrom :: forall x. Profile -> Rep Profile x
Prelude.Generic)

-- |
-- Create a value of 'Profile' 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:
--
-- 'accountNumber', 'profile_accountNumber' - A unique account number that you have given to the customer.
--
-- 'additionalInformation', 'profile_additionalInformation' - Any additional information relevant to the customer’s profile.
--
-- 'address', 'profile_address' - A generic address associated with the customer that is not mailing,
-- shipping, or billing.
--
-- 'attributes', 'profile_attributes' - A key value pair of attributes of a customer profile.
--
-- 'billingAddress', 'profile_billingAddress' - The customer’s billing address.
--
-- 'birthDate', 'profile_birthDate' - The customer’s birth date.
--
-- 'businessEmailAddress', 'profile_businessEmailAddress' - The customer’s business email address.
--
-- 'businessName', 'profile_businessName' - The name of the customer’s business.
--
-- 'businessPhoneNumber', 'profile_businessPhoneNumber' - The customer’s home phone number.
--
-- 'emailAddress', 'profile_emailAddress' - The customer’s email address, which has not been specified as a personal
-- or business address.
--
-- 'firstName', 'profile_firstName' - The customer’s first name.
--
-- 'foundByItems', 'profile_foundByItems' - A list of items used to find a profile returned in a
-- <https://docs.aws.amazon.com/customerprofiles/latest/APIReference/API_SearchProfiles.html SearchProfiles>
-- response. An item is a key-value(s) pair that matches an attribute in
-- the profile.
--
-- If the optional @AdditionalSearchKeys@ parameter was included in the
-- <https://docs.aws.amazon.com/customerprofiles/latest/APIReference/API_SearchProfiles.html SearchProfiles>
-- request, the @FoundByItems@ list should be interpreted based on the
-- @LogicalOperator@ used in the request:
--
-- -   @AND@ - The profile included in the response matched all of the
--     search keys specified in the request. The @FoundByItems@ will
--     include all of the key-value(s) pairs that were specified in the
--     request (as this is a requirement of @AND@ search logic).
--
-- -   @OR@ - The profile included in the response matched at least one of
--     the search keys specified in the request. The @FoundByItems@ will
--     include each of the key-value(s) pairs that the profile was found
--     by.
--
-- The @OR@ relationship is the default behavior if the @LogicalOperator@
-- parameter is not included in the
-- <https://docs.aws.amazon.com/customerprofiles/latest/APIReference/API_SearchProfiles.html SearchProfiles>
-- request.
--
-- 'gender', 'profile_gender' - The gender with which the customer identifies.
--
-- 'homePhoneNumber', 'profile_homePhoneNumber' - The customer’s home phone number.
--
-- 'lastName', 'profile_lastName' - The customer’s last name.
--
-- 'mailingAddress', 'profile_mailingAddress' - The customer’s mailing address.
--
-- 'middleName', 'profile_middleName' - The customer’s middle name.
--
-- 'mobilePhoneNumber', 'profile_mobilePhoneNumber' - The customer’s mobile phone number.
--
-- 'partyType', 'profile_partyType' - The type of profile used to describe the customer.
--
-- 'personalEmailAddress', 'profile_personalEmailAddress' - The customer’s personal email address.
--
-- 'phoneNumber', 'profile_phoneNumber' - The customer\'s phone number, which has not been specified as a mobile,
-- home, or business number.
--
-- 'profileId', 'profile_profileId' - The unique identifier of a customer profile.
--
-- 'shippingAddress', 'profile_shippingAddress' - The customer’s shipping address.
newProfile ::
  Profile
newProfile :: Profile
newProfile =
  Profile'
    { $sel:accountNumber:Profile' :: Maybe Text
accountNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:additionalInformation:Profile' :: Maybe Text
additionalInformation = forall a. Maybe a
Prelude.Nothing,
      $sel:address:Profile' :: Maybe Address
address = forall a. Maybe a
Prelude.Nothing,
      $sel:attributes:Profile' :: Maybe (HashMap Text Text)
attributes = forall a. Maybe a
Prelude.Nothing,
      $sel:billingAddress:Profile' :: Maybe Address
billingAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:birthDate:Profile' :: Maybe Text
birthDate = forall a. Maybe a
Prelude.Nothing,
      $sel:businessEmailAddress:Profile' :: Maybe Text
businessEmailAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:businessName:Profile' :: Maybe Text
businessName = forall a. Maybe a
Prelude.Nothing,
      $sel:businessPhoneNumber:Profile' :: Maybe Text
businessPhoneNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:emailAddress:Profile' :: Maybe Text
emailAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:firstName:Profile' :: Maybe Text
firstName = forall a. Maybe a
Prelude.Nothing,
      $sel:foundByItems:Profile' :: Maybe (NonEmpty FoundByKeyValue)
foundByItems = forall a. Maybe a
Prelude.Nothing,
      $sel:gender:Profile' :: Maybe Gender
gender = forall a. Maybe a
Prelude.Nothing,
      $sel:homePhoneNumber:Profile' :: Maybe Text
homePhoneNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:lastName:Profile' :: Maybe Text
lastName = forall a. Maybe a
Prelude.Nothing,
      $sel:mailingAddress:Profile' :: Maybe Address
mailingAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:middleName:Profile' :: Maybe Text
middleName = forall a. Maybe a
Prelude.Nothing,
      $sel:mobilePhoneNumber:Profile' :: Maybe Text
mobilePhoneNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:partyType:Profile' :: Maybe PartyType
partyType = forall a. Maybe a
Prelude.Nothing,
      $sel:personalEmailAddress:Profile' :: Maybe Text
personalEmailAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:phoneNumber:Profile' :: Maybe Text
phoneNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:profileId:Profile' :: Maybe Text
profileId = forall a. Maybe a
Prelude.Nothing,
      $sel:shippingAddress:Profile' :: Maybe Address
shippingAddress = forall a. Maybe a
Prelude.Nothing
    }

-- | A unique account number that you have given to the customer.
profile_accountNumber :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_accountNumber :: Lens' Profile (Maybe Text)
profile_accountNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
accountNumber :: Maybe Text
$sel:accountNumber:Profile' :: Profile -> Maybe Text
accountNumber} -> Maybe Text
accountNumber) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:accountNumber:Profile' :: Maybe Text
accountNumber = Maybe Text
a} :: Profile)

-- | Any additional information relevant to the customer’s profile.
profile_additionalInformation :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_additionalInformation :: Lens' Profile (Maybe Text)
profile_additionalInformation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
additionalInformation :: Maybe Text
$sel:additionalInformation:Profile' :: Profile -> Maybe Text
additionalInformation} -> Maybe Text
additionalInformation) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:additionalInformation:Profile' :: Maybe Text
additionalInformation = Maybe Text
a} :: Profile)

-- | A generic address associated with the customer that is not mailing,
-- shipping, or billing.
profile_address :: Lens.Lens' Profile (Prelude.Maybe Address)
profile_address :: Lens' Profile (Maybe Address)
profile_address = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Address
address :: Maybe Address
$sel:address:Profile' :: Profile -> Maybe Address
address} -> Maybe Address
address) (\s :: Profile
s@Profile' {} Maybe Address
a -> Profile
s {$sel:address:Profile' :: Maybe Address
address = Maybe Address
a} :: Profile)

-- | A key value pair of attributes of a customer profile.
profile_attributes :: Lens.Lens' Profile (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
profile_attributes :: Lens' Profile (Maybe (HashMap Text Text))
profile_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe (HashMap Text Text)
attributes :: Maybe (HashMap Text Text)
$sel:attributes:Profile' :: Profile -> Maybe (HashMap Text Text)
attributes} -> Maybe (HashMap Text Text)
attributes) (\s :: Profile
s@Profile' {} Maybe (HashMap Text Text)
a -> Profile
s {$sel:attributes:Profile' :: Maybe (HashMap Text Text)
attributes = Maybe (HashMap Text Text)
a} :: Profile) 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 customer’s billing address.
profile_billingAddress :: Lens.Lens' Profile (Prelude.Maybe Address)
profile_billingAddress :: Lens' Profile (Maybe Address)
profile_billingAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Address
billingAddress :: Maybe Address
$sel:billingAddress:Profile' :: Profile -> Maybe Address
billingAddress} -> Maybe Address
billingAddress) (\s :: Profile
s@Profile' {} Maybe Address
a -> Profile
s {$sel:billingAddress:Profile' :: Maybe Address
billingAddress = Maybe Address
a} :: Profile)

-- | The customer’s birth date.
profile_birthDate :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_birthDate :: Lens' Profile (Maybe Text)
profile_birthDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
birthDate :: Maybe Text
$sel:birthDate:Profile' :: Profile -> Maybe Text
birthDate} -> Maybe Text
birthDate) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:birthDate:Profile' :: Maybe Text
birthDate = Maybe Text
a} :: Profile)

-- | The customer’s business email address.
profile_businessEmailAddress :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_businessEmailAddress :: Lens' Profile (Maybe Text)
profile_businessEmailAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
businessEmailAddress :: Maybe Text
$sel:businessEmailAddress:Profile' :: Profile -> Maybe Text
businessEmailAddress} -> Maybe Text
businessEmailAddress) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:businessEmailAddress:Profile' :: Maybe Text
businessEmailAddress = Maybe Text
a} :: Profile)

-- | The name of the customer’s business.
profile_businessName :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_businessName :: Lens' Profile (Maybe Text)
profile_businessName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
businessName :: Maybe Text
$sel:businessName:Profile' :: Profile -> Maybe Text
businessName} -> Maybe Text
businessName) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:businessName:Profile' :: Maybe Text
businessName = Maybe Text
a} :: Profile)

-- | The customer’s home phone number.
profile_businessPhoneNumber :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_businessPhoneNumber :: Lens' Profile (Maybe Text)
profile_businessPhoneNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
businessPhoneNumber :: Maybe Text
$sel:businessPhoneNumber:Profile' :: Profile -> Maybe Text
businessPhoneNumber} -> Maybe Text
businessPhoneNumber) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:businessPhoneNumber:Profile' :: Maybe Text
businessPhoneNumber = Maybe Text
a} :: Profile)

-- | The customer’s email address, which has not been specified as a personal
-- or business address.
profile_emailAddress :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_emailAddress :: Lens' Profile (Maybe Text)
profile_emailAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
emailAddress :: Maybe Text
$sel:emailAddress:Profile' :: Profile -> Maybe Text
emailAddress} -> Maybe Text
emailAddress) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:emailAddress:Profile' :: Maybe Text
emailAddress = Maybe Text
a} :: Profile)

-- | The customer’s first name.
profile_firstName :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_firstName :: Lens' Profile (Maybe Text)
profile_firstName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
firstName :: Maybe Text
$sel:firstName:Profile' :: Profile -> Maybe Text
firstName} -> Maybe Text
firstName) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:firstName:Profile' :: Maybe Text
firstName = Maybe Text
a} :: Profile)

-- | A list of items used to find a profile returned in a
-- <https://docs.aws.amazon.com/customerprofiles/latest/APIReference/API_SearchProfiles.html SearchProfiles>
-- response. An item is a key-value(s) pair that matches an attribute in
-- the profile.
--
-- If the optional @AdditionalSearchKeys@ parameter was included in the
-- <https://docs.aws.amazon.com/customerprofiles/latest/APIReference/API_SearchProfiles.html SearchProfiles>
-- request, the @FoundByItems@ list should be interpreted based on the
-- @LogicalOperator@ used in the request:
--
-- -   @AND@ - The profile included in the response matched all of the
--     search keys specified in the request. The @FoundByItems@ will
--     include all of the key-value(s) pairs that were specified in the
--     request (as this is a requirement of @AND@ search logic).
--
-- -   @OR@ - The profile included in the response matched at least one of
--     the search keys specified in the request. The @FoundByItems@ will
--     include each of the key-value(s) pairs that the profile was found
--     by.
--
-- The @OR@ relationship is the default behavior if the @LogicalOperator@
-- parameter is not included in the
-- <https://docs.aws.amazon.com/customerprofiles/latest/APIReference/API_SearchProfiles.html SearchProfiles>
-- request.
profile_foundByItems :: Lens.Lens' Profile (Prelude.Maybe (Prelude.NonEmpty FoundByKeyValue))
profile_foundByItems :: Lens' Profile (Maybe (NonEmpty FoundByKeyValue))
profile_foundByItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe (NonEmpty FoundByKeyValue)
foundByItems :: Maybe (NonEmpty FoundByKeyValue)
$sel:foundByItems:Profile' :: Profile -> Maybe (NonEmpty FoundByKeyValue)
foundByItems} -> Maybe (NonEmpty FoundByKeyValue)
foundByItems) (\s :: Profile
s@Profile' {} Maybe (NonEmpty FoundByKeyValue)
a -> Profile
s {$sel:foundByItems:Profile' :: Maybe (NonEmpty FoundByKeyValue)
foundByItems = Maybe (NonEmpty FoundByKeyValue)
a} :: Profile) 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 gender with which the customer identifies.
profile_gender :: Lens.Lens' Profile (Prelude.Maybe Gender)
profile_gender :: Lens' Profile (Maybe Gender)
profile_gender = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Gender
gender :: Maybe Gender
$sel:gender:Profile' :: Profile -> Maybe Gender
gender} -> Maybe Gender
gender) (\s :: Profile
s@Profile' {} Maybe Gender
a -> Profile
s {$sel:gender:Profile' :: Maybe Gender
gender = Maybe Gender
a} :: Profile)

-- | The customer’s home phone number.
profile_homePhoneNumber :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_homePhoneNumber :: Lens' Profile (Maybe Text)
profile_homePhoneNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
homePhoneNumber :: Maybe Text
$sel:homePhoneNumber:Profile' :: Profile -> Maybe Text
homePhoneNumber} -> Maybe Text
homePhoneNumber) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:homePhoneNumber:Profile' :: Maybe Text
homePhoneNumber = Maybe Text
a} :: Profile)

-- | The customer’s last name.
profile_lastName :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_lastName :: Lens' Profile (Maybe Text)
profile_lastName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
lastName :: Maybe Text
$sel:lastName:Profile' :: Profile -> Maybe Text
lastName} -> Maybe Text
lastName) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:lastName:Profile' :: Maybe Text
lastName = Maybe Text
a} :: Profile)

-- | The customer’s mailing address.
profile_mailingAddress :: Lens.Lens' Profile (Prelude.Maybe Address)
profile_mailingAddress :: Lens' Profile (Maybe Address)
profile_mailingAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Address
mailingAddress :: Maybe Address
$sel:mailingAddress:Profile' :: Profile -> Maybe Address
mailingAddress} -> Maybe Address
mailingAddress) (\s :: Profile
s@Profile' {} Maybe Address
a -> Profile
s {$sel:mailingAddress:Profile' :: Maybe Address
mailingAddress = Maybe Address
a} :: Profile)

-- | The customer’s middle name.
profile_middleName :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_middleName :: Lens' Profile (Maybe Text)
profile_middleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
middleName :: Maybe Text
$sel:middleName:Profile' :: Profile -> Maybe Text
middleName} -> Maybe Text
middleName) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:middleName:Profile' :: Maybe Text
middleName = Maybe Text
a} :: Profile)

-- | The customer’s mobile phone number.
profile_mobilePhoneNumber :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_mobilePhoneNumber :: Lens' Profile (Maybe Text)
profile_mobilePhoneNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
mobilePhoneNumber :: Maybe Text
$sel:mobilePhoneNumber:Profile' :: Profile -> Maybe Text
mobilePhoneNumber} -> Maybe Text
mobilePhoneNumber) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:mobilePhoneNumber:Profile' :: Maybe Text
mobilePhoneNumber = Maybe Text
a} :: Profile)

-- | The type of profile used to describe the customer.
profile_partyType :: Lens.Lens' Profile (Prelude.Maybe PartyType)
profile_partyType :: Lens' Profile (Maybe PartyType)
profile_partyType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe PartyType
partyType :: Maybe PartyType
$sel:partyType:Profile' :: Profile -> Maybe PartyType
partyType} -> Maybe PartyType
partyType) (\s :: Profile
s@Profile' {} Maybe PartyType
a -> Profile
s {$sel:partyType:Profile' :: Maybe PartyType
partyType = Maybe PartyType
a} :: Profile)

-- | The customer’s personal email address.
profile_personalEmailAddress :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_personalEmailAddress :: Lens' Profile (Maybe Text)
profile_personalEmailAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
personalEmailAddress :: Maybe Text
$sel:personalEmailAddress:Profile' :: Profile -> Maybe Text
personalEmailAddress} -> Maybe Text
personalEmailAddress) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:personalEmailAddress:Profile' :: Maybe Text
personalEmailAddress = Maybe Text
a} :: Profile)

-- | The customer\'s phone number, which has not been specified as a mobile,
-- home, or business number.
profile_phoneNumber :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_phoneNumber :: Lens' Profile (Maybe Text)
profile_phoneNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
phoneNumber :: Maybe Text
$sel:phoneNumber:Profile' :: Profile -> Maybe Text
phoneNumber} -> Maybe Text
phoneNumber) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:phoneNumber:Profile' :: Maybe Text
phoneNumber = Maybe Text
a} :: Profile)

-- | The unique identifier of a customer profile.
profile_profileId :: Lens.Lens' Profile (Prelude.Maybe Prelude.Text)
profile_profileId :: Lens' Profile (Maybe Text)
profile_profileId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Text
profileId :: Maybe Text
$sel:profileId:Profile' :: Profile -> Maybe Text
profileId} -> Maybe Text
profileId) (\s :: Profile
s@Profile' {} Maybe Text
a -> Profile
s {$sel:profileId:Profile' :: Maybe Text
profileId = Maybe Text
a} :: Profile)

-- | The customer’s shipping address.
profile_shippingAddress :: Lens.Lens' Profile (Prelude.Maybe Address)
profile_shippingAddress :: Lens' Profile (Maybe Address)
profile_shippingAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Profile' {Maybe Address
shippingAddress :: Maybe Address
$sel:shippingAddress:Profile' :: Profile -> Maybe Address
shippingAddress} -> Maybe Address
shippingAddress) (\s :: Profile
s@Profile' {} Maybe Address
a -> Profile
s {$sel:shippingAddress:Profile' :: Maybe Address
shippingAddress = Maybe Address
a} :: Profile)

instance Data.FromJSON Profile where
  parseJSON :: Value -> Parser Profile
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Profile"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Address
-> Maybe (HashMap Text Text)
-> Maybe Address
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe (NonEmpty FoundByKeyValue)
-> Maybe Gender
-> Maybe Text
-> Maybe Text
-> Maybe Address
-> Maybe Text
-> Maybe Text
-> Maybe PartyType
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Address
-> Profile
Profile'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AccountNumber")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AdditionalInformation")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (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 -> Parser (Maybe a)
Data..:? Key
"Attributes" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"BillingAddress")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"BirthDate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"BusinessEmailAddress")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"BusinessName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"BusinessPhoneNumber")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"EmailAddress")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FirstName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FoundByItems")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Gender")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"HomePhoneNumber")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"LastName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MailingAddress")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MiddleName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MobilePhoneNumber")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"PartyType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"PersonalEmailAddress")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (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 -> Parser (Maybe a)
Data..:? Key
"ProfileId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ShippingAddress")
      )

instance Prelude.Hashable Profile where
  hashWithSalt :: Int -> Profile -> Int
hashWithSalt Int
_salt Profile' {Maybe (NonEmpty FoundByKeyValue)
Maybe Text
Maybe (HashMap Text Text)
Maybe Address
Maybe Gender
Maybe PartyType
shippingAddress :: Maybe Address
profileId :: Maybe Text
phoneNumber :: Maybe Text
personalEmailAddress :: Maybe Text
partyType :: Maybe PartyType
mobilePhoneNumber :: Maybe Text
middleName :: Maybe Text
mailingAddress :: Maybe Address
lastName :: Maybe Text
homePhoneNumber :: Maybe Text
gender :: Maybe Gender
foundByItems :: Maybe (NonEmpty FoundByKeyValue)
firstName :: Maybe Text
emailAddress :: Maybe Text
businessPhoneNumber :: Maybe Text
businessName :: Maybe Text
businessEmailAddress :: Maybe Text
birthDate :: Maybe Text
billingAddress :: Maybe Address
attributes :: Maybe (HashMap Text Text)
address :: Maybe Address
additionalInformation :: Maybe Text
accountNumber :: Maybe Text
$sel:shippingAddress:Profile' :: Profile -> Maybe Address
$sel:profileId:Profile' :: Profile -> Maybe Text
$sel:phoneNumber:Profile' :: Profile -> Maybe Text
$sel:personalEmailAddress:Profile' :: Profile -> Maybe Text
$sel:partyType:Profile' :: Profile -> Maybe PartyType
$sel:mobilePhoneNumber:Profile' :: Profile -> Maybe Text
$sel:middleName:Profile' :: Profile -> Maybe Text
$sel:mailingAddress:Profile' :: Profile -> Maybe Address
$sel:lastName:Profile' :: Profile -> Maybe Text
$sel:homePhoneNumber:Profile' :: Profile -> Maybe Text
$sel:gender:Profile' :: Profile -> Maybe Gender
$sel:foundByItems:Profile' :: Profile -> Maybe (NonEmpty FoundByKeyValue)
$sel:firstName:Profile' :: Profile -> Maybe Text
$sel:emailAddress:Profile' :: Profile -> Maybe Text
$sel:businessPhoneNumber:Profile' :: Profile -> Maybe Text
$sel:businessName:Profile' :: Profile -> Maybe Text
$sel:businessEmailAddress:Profile' :: Profile -> Maybe Text
$sel:birthDate:Profile' :: Profile -> Maybe Text
$sel:billingAddress:Profile' :: Profile -> Maybe Address
$sel:attributes:Profile' :: Profile -> Maybe (HashMap Text Text)
$sel:address:Profile' :: Profile -> Maybe Address
$sel:additionalInformation:Profile' :: Profile -> Maybe Text
$sel:accountNumber:Profile' :: Profile -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
accountNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
additionalInformation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Address
address
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
attributes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Address
billingAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
birthDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
businessEmailAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
businessName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
businessPhoneNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
emailAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
firstName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty FoundByKeyValue)
foundByItems
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Gender
gender
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
homePhoneNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
lastName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Address
mailingAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
middleName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
mobilePhoneNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PartyType
partyType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
personalEmailAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
phoneNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
profileId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Address
shippingAddress

instance Prelude.NFData Profile where
  rnf :: Profile -> ()
rnf Profile' {Maybe (NonEmpty FoundByKeyValue)
Maybe Text
Maybe (HashMap Text Text)
Maybe Address
Maybe Gender
Maybe PartyType
shippingAddress :: Maybe Address
profileId :: Maybe Text
phoneNumber :: Maybe Text
personalEmailAddress :: Maybe Text
partyType :: Maybe PartyType
mobilePhoneNumber :: Maybe Text
middleName :: Maybe Text
mailingAddress :: Maybe Address
lastName :: Maybe Text
homePhoneNumber :: Maybe Text
gender :: Maybe Gender
foundByItems :: Maybe (NonEmpty FoundByKeyValue)
firstName :: Maybe Text
emailAddress :: Maybe Text
businessPhoneNumber :: Maybe Text
businessName :: Maybe Text
businessEmailAddress :: Maybe Text
birthDate :: Maybe Text
billingAddress :: Maybe Address
attributes :: Maybe (HashMap Text Text)
address :: Maybe Address
additionalInformation :: Maybe Text
accountNumber :: Maybe Text
$sel:shippingAddress:Profile' :: Profile -> Maybe Address
$sel:profileId:Profile' :: Profile -> Maybe Text
$sel:phoneNumber:Profile' :: Profile -> Maybe Text
$sel:personalEmailAddress:Profile' :: Profile -> Maybe Text
$sel:partyType:Profile' :: Profile -> Maybe PartyType
$sel:mobilePhoneNumber:Profile' :: Profile -> Maybe Text
$sel:middleName:Profile' :: Profile -> Maybe Text
$sel:mailingAddress:Profile' :: Profile -> Maybe Address
$sel:lastName:Profile' :: Profile -> Maybe Text
$sel:homePhoneNumber:Profile' :: Profile -> Maybe Text
$sel:gender:Profile' :: Profile -> Maybe Gender
$sel:foundByItems:Profile' :: Profile -> Maybe (NonEmpty FoundByKeyValue)
$sel:firstName:Profile' :: Profile -> Maybe Text
$sel:emailAddress:Profile' :: Profile -> Maybe Text
$sel:businessPhoneNumber:Profile' :: Profile -> Maybe Text
$sel:businessName:Profile' :: Profile -> Maybe Text
$sel:businessEmailAddress:Profile' :: Profile -> Maybe Text
$sel:birthDate:Profile' :: Profile -> Maybe Text
$sel:billingAddress:Profile' :: Profile -> Maybe Address
$sel:attributes:Profile' :: Profile -> Maybe (HashMap Text Text)
$sel:address:Profile' :: Profile -> Maybe Address
$sel:additionalInformation:Profile' :: Profile -> Maybe Text
$sel:accountNumber:Profile' :: Profile -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
accountNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
additionalInformation
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 (HashMap Text Text)
attributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Address
billingAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
birthDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
businessEmailAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
businessName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
businessPhoneNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
emailAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
firstName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty FoundByKeyValue)
foundByItems
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Gender
gender
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
homePhoneNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Address
mailingAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
middleName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
mobilePhoneNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PartyType
partyType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
personalEmailAddress
      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
profileId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Address
shippingAddress