{-# 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.FieldSourceProfileIds
-- 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.FieldSourceProfileIds where

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

-- | A duplicate customer profile that is to be merged into a main profile.
--
-- /See:/ 'newFieldSourceProfileIds' smart constructor.
data FieldSourceProfileIds = FieldSourceProfileIds'
  { -- | A unique identifier for the account number field to be merged.
    FieldSourceProfileIds -> Maybe Text
accountNumber :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the additional information field to be merged.
    FieldSourceProfileIds -> Maybe Text
additionalInformation :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the party type field to be merged.
    FieldSourceProfileIds -> Maybe Text
address :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the attributes field to be merged.
    FieldSourceProfileIds -> Maybe (HashMap Text Text)
attributes :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | A unique identifier for the billing type field to be merged.
    FieldSourceProfileIds -> Maybe Text
billingAddress :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the birthdate field to be merged.
    FieldSourceProfileIds -> Maybe Text
birthDate :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the party type field to be merged.
    FieldSourceProfileIds -> Maybe Text
businessEmailAddress :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the business name field to be merged.
    FieldSourceProfileIds -> Maybe Text
businessName :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the business phone number field to be merged.
    FieldSourceProfileIds -> Maybe Text
businessPhoneNumber :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the email address field to be merged.
    FieldSourceProfileIds -> Maybe Text
emailAddress :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the first name field to be merged.
    FieldSourceProfileIds -> Maybe Text
firstName :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the gender field to be merged.
    FieldSourceProfileIds -> Maybe Text
gender :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the home phone number field to be merged.
    FieldSourceProfileIds -> Maybe Text
homePhoneNumber :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the last name field to be merged.
    FieldSourceProfileIds -> Maybe Text
lastName :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the mailing address field to be merged.
    FieldSourceProfileIds -> Maybe Text
mailingAddress :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the middle name field to be merged.
    FieldSourceProfileIds -> Maybe Text
middleName :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the mobile phone number field to be merged.
    FieldSourceProfileIds -> Maybe Text
mobilePhoneNumber :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the party type field to be merged.
    FieldSourceProfileIds -> Maybe Text
partyType :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the personal email address field to be merged.
    FieldSourceProfileIds -> Maybe Text
personalEmailAddress :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the phone number field to be merged.
    FieldSourceProfileIds -> Maybe Text
phoneNumber :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the shipping address field to be merged.
    FieldSourceProfileIds -> Maybe Text
shippingAddress :: Prelude.Maybe Prelude.Text
  }
  deriving (FieldSourceProfileIds -> FieldSourceProfileIds -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldSourceProfileIds -> FieldSourceProfileIds -> Bool
$c/= :: FieldSourceProfileIds -> FieldSourceProfileIds -> Bool
== :: FieldSourceProfileIds -> FieldSourceProfileIds -> Bool
$c== :: FieldSourceProfileIds -> FieldSourceProfileIds -> Bool
Prelude.Eq, ReadPrec [FieldSourceProfileIds]
ReadPrec FieldSourceProfileIds
Int -> ReadS FieldSourceProfileIds
ReadS [FieldSourceProfileIds]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldSourceProfileIds]
$creadListPrec :: ReadPrec [FieldSourceProfileIds]
readPrec :: ReadPrec FieldSourceProfileIds
$creadPrec :: ReadPrec FieldSourceProfileIds
readList :: ReadS [FieldSourceProfileIds]
$creadList :: ReadS [FieldSourceProfileIds]
readsPrec :: Int -> ReadS FieldSourceProfileIds
$creadsPrec :: Int -> ReadS FieldSourceProfileIds
Prelude.Read, Int -> FieldSourceProfileIds -> ShowS
[FieldSourceProfileIds] -> ShowS
FieldSourceProfileIds -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FieldSourceProfileIds] -> ShowS
$cshowList :: [FieldSourceProfileIds] -> ShowS
show :: FieldSourceProfileIds -> String
$cshow :: FieldSourceProfileIds -> String
showsPrec :: Int -> FieldSourceProfileIds -> ShowS
$cshowsPrec :: Int -> FieldSourceProfileIds -> ShowS
Prelude.Show, forall x. Rep FieldSourceProfileIds x -> FieldSourceProfileIds
forall x. FieldSourceProfileIds -> Rep FieldSourceProfileIds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FieldSourceProfileIds x -> FieldSourceProfileIds
$cfrom :: forall x. FieldSourceProfileIds -> Rep FieldSourceProfileIds x
Prelude.Generic)

-- |
-- Create a value of 'FieldSourceProfileIds' 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', 'fieldSourceProfileIds_accountNumber' - A unique identifier for the account number field to be merged.
--
-- 'additionalInformation', 'fieldSourceProfileIds_additionalInformation' - A unique identifier for the additional information field to be merged.
--
-- 'address', 'fieldSourceProfileIds_address' - A unique identifier for the party type field to be merged.
--
-- 'attributes', 'fieldSourceProfileIds_attributes' - A unique identifier for the attributes field to be merged.
--
-- 'billingAddress', 'fieldSourceProfileIds_billingAddress' - A unique identifier for the billing type field to be merged.
--
-- 'birthDate', 'fieldSourceProfileIds_birthDate' - A unique identifier for the birthdate field to be merged.
--
-- 'businessEmailAddress', 'fieldSourceProfileIds_businessEmailAddress' - A unique identifier for the party type field to be merged.
--
-- 'businessName', 'fieldSourceProfileIds_businessName' - A unique identifier for the business name field to be merged.
--
-- 'businessPhoneNumber', 'fieldSourceProfileIds_businessPhoneNumber' - A unique identifier for the business phone number field to be merged.
--
-- 'emailAddress', 'fieldSourceProfileIds_emailAddress' - A unique identifier for the email address field to be merged.
--
-- 'firstName', 'fieldSourceProfileIds_firstName' - A unique identifier for the first name field to be merged.
--
-- 'gender', 'fieldSourceProfileIds_gender' - A unique identifier for the gender field to be merged.
--
-- 'homePhoneNumber', 'fieldSourceProfileIds_homePhoneNumber' - A unique identifier for the home phone number field to be merged.
--
-- 'lastName', 'fieldSourceProfileIds_lastName' - A unique identifier for the last name field to be merged.
--
-- 'mailingAddress', 'fieldSourceProfileIds_mailingAddress' - A unique identifier for the mailing address field to be merged.
--
-- 'middleName', 'fieldSourceProfileIds_middleName' - A unique identifier for the middle name field to be merged.
--
-- 'mobilePhoneNumber', 'fieldSourceProfileIds_mobilePhoneNumber' - A unique identifier for the mobile phone number field to be merged.
--
-- 'partyType', 'fieldSourceProfileIds_partyType' - A unique identifier for the party type field to be merged.
--
-- 'personalEmailAddress', 'fieldSourceProfileIds_personalEmailAddress' - A unique identifier for the personal email address field to be merged.
--
-- 'phoneNumber', 'fieldSourceProfileIds_phoneNumber' - A unique identifier for the phone number field to be merged.
--
-- 'shippingAddress', 'fieldSourceProfileIds_shippingAddress' - A unique identifier for the shipping address field to be merged.
newFieldSourceProfileIds ::
  FieldSourceProfileIds
newFieldSourceProfileIds :: FieldSourceProfileIds
newFieldSourceProfileIds =
  FieldSourceProfileIds'
    { $sel:accountNumber:FieldSourceProfileIds' :: Maybe Text
accountNumber =
        forall a. Maybe a
Prelude.Nothing,
      $sel:additionalInformation:FieldSourceProfileIds' :: Maybe Text
additionalInformation = forall a. Maybe a
Prelude.Nothing,
      $sel:address:FieldSourceProfileIds' :: Maybe Text
address = forall a. Maybe a
Prelude.Nothing,
      $sel:attributes:FieldSourceProfileIds' :: Maybe (HashMap Text Text)
attributes = forall a. Maybe a
Prelude.Nothing,
      $sel:billingAddress:FieldSourceProfileIds' :: Maybe Text
billingAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:birthDate:FieldSourceProfileIds' :: Maybe Text
birthDate = forall a. Maybe a
Prelude.Nothing,
      $sel:businessEmailAddress:FieldSourceProfileIds' :: Maybe Text
businessEmailAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:businessName:FieldSourceProfileIds' :: Maybe Text
businessName = forall a. Maybe a
Prelude.Nothing,
      $sel:businessPhoneNumber:FieldSourceProfileIds' :: Maybe Text
businessPhoneNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:emailAddress:FieldSourceProfileIds' :: Maybe Text
emailAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:firstName:FieldSourceProfileIds' :: Maybe Text
firstName = forall a. Maybe a
Prelude.Nothing,
      $sel:gender:FieldSourceProfileIds' :: Maybe Text
gender = forall a. Maybe a
Prelude.Nothing,
      $sel:homePhoneNumber:FieldSourceProfileIds' :: Maybe Text
homePhoneNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:lastName:FieldSourceProfileIds' :: Maybe Text
lastName = forall a. Maybe a
Prelude.Nothing,
      $sel:mailingAddress:FieldSourceProfileIds' :: Maybe Text
mailingAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:middleName:FieldSourceProfileIds' :: Maybe Text
middleName = forall a. Maybe a
Prelude.Nothing,
      $sel:mobilePhoneNumber:FieldSourceProfileIds' :: Maybe Text
mobilePhoneNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:partyType:FieldSourceProfileIds' :: Maybe Text
partyType = forall a. Maybe a
Prelude.Nothing,
      $sel:personalEmailAddress:FieldSourceProfileIds' :: Maybe Text
personalEmailAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:phoneNumber:FieldSourceProfileIds' :: Maybe Text
phoneNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:shippingAddress:FieldSourceProfileIds' :: Maybe Text
shippingAddress = forall a. Maybe a
Prelude.Nothing
    }

-- | A unique identifier for the account number field to be merged.
fieldSourceProfileIds_accountNumber :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_accountNumber :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_accountNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
accountNumber :: Maybe Text
$sel:accountNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
accountNumber} -> Maybe Text
accountNumber) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:accountNumber:FieldSourceProfileIds' :: Maybe Text
accountNumber = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the additional information field to be merged.
fieldSourceProfileIds_additionalInformation :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_additionalInformation :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_additionalInformation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
additionalInformation :: Maybe Text
$sel:additionalInformation:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
additionalInformation} -> Maybe Text
additionalInformation) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:additionalInformation:FieldSourceProfileIds' :: Maybe Text
additionalInformation = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the party type field to be merged.
fieldSourceProfileIds_address :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_address :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_address = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
address :: Maybe Text
$sel:address:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
address} -> Maybe Text
address) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:address:FieldSourceProfileIds' :: Maybe Text
address = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the attributes field to be merged.
fieldSourceProfileIds_attributes :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
fieldSourceProfileIds_attributes :: Lens' FieldSourceProfileIds (Maybe (HashMap Text Text))
fieldSourceProfileIds_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe (HashMap Text Text)
attributes :: Maybe (HashMap Text Text)
$sel:attributes:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe (HashMap Text Text)
attributes} -> Maybe (HashMap Text Text)
attributes) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe (HashMap Text Text)
a -> FieldSourceProfileIds
s {$sel:attributes:FieldSourceProfileIds' :: Maybe (HashMap Text Text)
attributes = Maybe (HashMap Text Text)
a} :: FieldSourceProfileIds) 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

-- | A unique identifier for the billing type field to be merged.
fieldSourceProfileIds_billingAddress :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_billingAddress :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_billingAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
billingAddress :: Maybe Text
$sel:billingAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
billingAddress} -> Maybe Text
billingAddress) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:billingAddress:FieldSourceProfileIds' :: Maybe Text
billingAddress = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the birthdate field to be merged.
fieldSourceProfileIds_birthDate :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_birthDate :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_birthDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
birthDate :: Maybe Text
$sel:birthDate:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
birthDate} -> Maybe Text
birthDate) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:birthDate:FieldSourceProfileIds' :: Maybe Text
birthDate = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the party type field to be merged.
fieldSourceProfileIds_businessEmailAddress :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_businessEmailAddress :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_businessEmailAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
businessEmailAddress :: Maybe Text
$sel:businessEmailAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
businessEmailAddress} -> Maybe Text
businessEmailAddress) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:businessEmailAddress:FieldSourceProfileIds' :: Maybe Text
businessEmailAddress = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the business name field to be merged.
fieldSourceProfileIds_businessName :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_businessName :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_businessName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
businessName :: Maybe Text
$sel:businessName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
businessName} -> Maybe Text
businessName) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:businessName:FieldSourceProfileIds' :: Maybe Text
businessName = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the business phone number field to be merged.
fieldSourceProfileIds_businessPhoneNumber :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_businessPhoneNumber :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_businessPhoneNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
businessPhoneNumber :: Maybe Text
$sel:businessPhoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
businessPhoneNumber} -> Maybe Text
businessPhoneNumber) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:businessPhoneNumber:FieldSourceProfileIds' :: Maybe Text
businessPhoneNumber = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the email address field to be merged.
fieldSourceProfileIds_emailAddress :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_emailAddress :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_emailAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
emailAddress :: Maybe Text
$sel:emailAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
emailAddress} -> Maybe Text
emailAddress) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:emailAddress:FieldSourceProfileIds' :: Maybe Text
emailAddress = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the first name field to be merged.
fieldSourceProfileIds_firstName :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_firstName :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_firstName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
firstName :: Maybe Text
$sel:firstName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
firstName} -> Maybe Text
firstName) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:firstName:FieldSourceProfileIds' :: Maybe Text
firstName = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the gender field to be merged.
fieldSourceProfileIds_gender :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_gender :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_gender = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
gender :: Maybe Text
$sel:gender:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
gender} -> Maybe Text
gender) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:gender:FieldSourceProfileIds' :: Maybe Text
gender = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the home phone number field to be merged.
fieldSourceProfileIds_homePhoneNumber :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_homePhoneNumber :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_homePhoneNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
homePhoneNumber :: Maybe Text
$sel:homePhoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
homePhoneNumber} -> Maybe Text
homePhoneNumber) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:homePhoneNumber:FieldSourceProfileIds' :: Maybe Text
homePhoneNumber = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the last name field to be merged.
fieldSourceProfileIds_lastName :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_lastName :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_lastName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
lastName :: Maybe Text
$sel:lastName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
lastName} -> Maybe Text
lastName) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:lastName:FieldSourceProfileIds' :: Maybe Text
lastName = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the mailing address field to be merged.
fieldSourceProfileIds_mailingAddress :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_mailingAddress :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_mailingAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
mailingAddress :: Maybe Text
$sel:mailingAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
mailingAddress} -> Maybe Text
mailingAddress) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:mailingAddress:FieldSourceProfileIds' :: Maybe Text
mailingAddress = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the middle name field to be merged.
fieldSourceProfileIds_middleName :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_middleName :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_middleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
middleName :: Maybe Text
$sel:middleName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
middleName} -> Maybe Text
middleName) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:middleName:FieldSourceProfileIds' :: Maybe Text
middleName = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the mobile phone number field to be merged.
fieldSourceProfileIds_mobilePhoneNumber :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_mobilePhoneNumber :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_mobilePhoneNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
mobilePhoneNumber :: Maybe Text
$sel:mobilePhoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
mobilePhoneNumber} -> Maybe Text
mobilePhoneNumber) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:mobilePhoneNumber:FieldSourceProfileIds' :: Maybe Text
mobilePhoneNumber = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the party type field to be merged.
fieldSourceProfileIds_partyType :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_partyType :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_partyType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
partyType :: Maybe Text
$sel:partyType:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
partyType} -> Maybe Text
partyType) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:partyType:FieldSourceProfileIds' :: Maybe Text
partyType = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the personal email address field to be merged.
fieldSourceProfileIds_personalEmailAddress :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_personalEmailAddress :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_personalEmailAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
personalEmailAddress :: Maybe Text
$sel:personalEmailAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
personalEmailAddress} -> Maybe Text
personalEmailAddress) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:personalEmailAddress:FieldSourceProfileIds' :: Maybe Text
personalEmailAddress = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the phone number field to be merged.
fieldSourceProfileIds_phoneNumber :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_phoneNumber :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_phoneNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
phoneNumber :: Maybe Text
$sel:phoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
phoneNumber} -> Maybe Text
phoneNumber) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:phoneNumber:FieldSourceProfileIds' :: Maybe Text
phoneNumber = Maybe Text
a} :: FieldSourceProfileIds)

-- | A unique identifier for the shipping address field to be merged.
fieldSourceProfileIds_shippingAddress :: Lens.Lens' FieldSourceProfileIds (Prelude.Maybe Prelude.Text)
fieldSourceProfileIds_shippingAddress :: Lens' FieldSourceProfileIds (Maybe Text)
fieldSourceProfileIds_shippingAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FieldSourceProfileIds' {Maybe Text
shippingAddress :: Maybe Text
$sel:shippingAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
shippingAddress} -> Maybe Text
shippingAddress) (\s :: FieldSourceProfileIds
s@FieldSourceProfileIds' {} Maybe Text
a -> FieldSourceProfileIds
s {$sel:shippingAddress:FieldSourceProfileIds' :: Maybe Text
shippingAddress = Maybe Text
a} :: FieldSourceProfileIds)

instance Prelude.Hashable FieldSourceProfileIds where
  hashWithSalt :: Int -> FieldSourceProfileIds -> Int
hashWithSalt Int
_salt FieldSourceProfileIds' {Maybe Text
Maybe (HashMap Text Text)
shippingAddress :: Maybe Text
phoneNumber :: Maybe Text
personalEmailAddress :: Maybe Text
partyType :: Maybe Text
mobilePhoneNumber :: Maybe Text
middleName :: Maybe Text
mailingAddress :: Maybe Text
lastName :: Maybe Text
homePhoneNumber :: Maybe Text
gender :: Maybe Text
firstName :: Maybe Text
emailAddress :: Maybe Text
businessPhoneNumber :: Maybe Text
businessName :: Maybe Text
businessEmailAddress :: Maybe Text
birthDate :: Maybe Text
billingAddress :: Maybe Text
attributes :: Maybe (HashMap Text Text)
address :: Maybe Text
additionalInformation :: Maybe Text
accountNumber :: Maybe Text
$sel:shippingAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:phoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:personalEmailAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:partyType:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:mobilePhoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:middleName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:mailingAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:lastName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:homePhoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:gender:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:firstName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:emailAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:businessPhoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:businessName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:businessEmailAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:birthDate:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:billingAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:attributes:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe (HashMap Text Text)
$sel:address:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:additionalInformation:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:accountNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> 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 Text
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 Text
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 Text
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 Text
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 Text
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
shippingAddress

instance Prelude.NFData FieldSourceProfileIds where
  rnf :: FieldSourceProfileIds -> ()
rnf FieldSourceProfileIds' {Maybe Text
Maybe (HashMap Text Text)
shippingAddress :: Maybe Text
phoneNumber :: Maybe Text
personalEmailAddress :: Maybe Text
partyType :: Maybe Text
mobilePhoneNumber :: Maybe Text
middleName :: Maybe Text
mailingAddress :: Maybe Text
lastName :: Maybe Text
homePhoneNumber :: Maybe Text
gender :: Maybe Text
firstName :: Maybe Text
emailAddress :: Maybe Text
businessPhoneNumber :: Maybe Text
businessName :: Maybe Text
businessEmailAddress :: Maybe Text
birthDate :: Maybe Text
billingAddress :: Maybe Text
attributes :: Maybe (HashMap Text Text)
address :: Maybe Text
additionalInformation :: Maybe Text
accountNumber :: Maybe Text
$sel:shippingAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:phoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:personalEmailAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:partyType:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:mobilePhoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:middleName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:mailingAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:lastName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:homePhoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:gender:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:firstName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:emailAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:businessPhoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:businessName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:businessEmailAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:birthDate:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:billingAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:attributes:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe (HashMap Text Text)
$sel:address:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:additionalInformation:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:accountNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> 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 Text
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 Text
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 Text
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 Text
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 Text
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
shippingAddress

instance Data.ToJSON FieldSourceProfileIds where
  toJSON :: FieldSourceProfileIds -> Value
toJSON FieldSourceProfileIds' {Maybe Text
Maybe (HashMap Text Text)
shippingAddress :: Maybe Text
phoneNumber :: Maybe Text
personalEmailAddress :: Maybe Text
partyType :: Maybe Text
mobilePhoneNumber :: Maybe Text
middleName :: Maybe Text
mailingAddress :: Maybe Text
lastName :: Maybe Text
homePhoneNumber :: Maybe Text
gender :: Maybe Text
firstName :: Maybe Text
emailAddress :: Maybe Text
businessPhoneNumber :: Maybe Text
businessName :: Maybe Text
businessEmailAddress :: Maybe Text
birthDate :: Maybe Text
billingAddress :: Maybe Text
attributes :: Maybe (HashMap Text Text)
address :: Maybe Text
additionalInformation :: Maybe Text
accountNumber :: Maybe Text
$sel:shippingAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:phoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:personalEmailAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:partyType:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:mobilePhoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:middleName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:mailingAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:lastName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:homePhoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:gender:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:firstName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:emailAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:businessPhoneNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:businessName:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:businessEmailAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:birthDate:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:billingAddress:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:attributes:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe (HashMap Text Text)
$sel:address:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:additionalInformation:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
$sel:accountNumber:FieldSourceProfileIds' :: FieldSourceProfileIds -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AccountNumber" 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
accountNumber,
            (Key
"AdditionalInformation" 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
additionalInformation,
            (Key
"Address" 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
address,
            (Key
"Attributes" 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)
attributes,
            (Key
"BillingAddress" 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
billingAddress,
            (Key
"BirthDate" 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
birthDate,
            (Key
"BusinessEmailAddress" 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
businessEmailAddress,
            (Key
"BusinessName" 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
businessName,
            (Key
"BusinessPhoneNumber" 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
businessPhoneNumber,
            (Key
"EmailAddress" 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
emailAddress,
            (Key
"FirstName" 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
firstName,
            (Key
"Gender" 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
gender,
            (Key
"HomePhoneNumber" 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
homePhoneNumber,
            (Key
"LastName" 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
lastName,
            (Key
"MailingAddress" 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
mailingAddress,
            (Key
"MiddleName" 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
middleName,
            (Key
"MobilePhoneNumber" 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
mobilePhoneNumber,
            (Key
"PartyType" 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
partyType,
            (Key
"PersonalEmailAddress" 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
personalEmailAddress,
            (Key
"PhoneNumber" 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
phoneNumber,
            (Key
"ShippingAddress" 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
shippingAddress
          ]
      )