{-# 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.Pinpoint.Types.EndpointBatchItem
-- 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.Pinpoint.Types.EndpointBatchItem where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Pinpoint.Types.ChannelType
import Amazonka.Pinpoint.Types.EndpointDemographic
import Amazonka.Pinpoint.Types.EndpointLocation
import Amazonka.Pinpoint.Types.EndpointUser
import qualified Amazonka.Prelude as Prelude

-- | Specifies an endpoint to create or update and the settings and
-- attributes to set or change for the endpoint.
--
-- /See:/ 'newEndpointBatchItem' smart constructor.
data EndpointBatchItem = EndpointBatchItem'
  { -- | The destination address for messages or push notifications that you send
    -- to the endpoint. The address varies by channel. For a push-notification
    -- channel, use the token provided by the push notification service, such
    -- as an Apple Push Notification service (APNs) device token or a Firebase
    -- Cloud Messaging (FCM) registration token. For the SMS channel, use a
    -- phone number in E.164 format, such as +12065550100. For the email
    -- channel, use an email address.
    EndpointBatchItem -> Maybe Text
address :: Prelude.Maybe Prelude.Text,
    -- | One or more custom attributes that describe the endpoint by associating
    -- a name with an array of values. For example, the value of a custom
    -- attribute named Interests might be: [\"Science\", \"Music\",
    -- \"Travel\"]. You can use these attributes as filter criteria when you
    -- create segments. Attribute names are case sensitive.
    --
    -- An attribute name can contain up to 50 characters. An attribute value
    -- can contain up to 100 characters. When you define the name of a custom
    -- attribute, avoid using the following characters: number sign (#), colon
    -- (:), question mark (?), backslash (\\), and slash (\/). The Amazon
    -- Pinpoint console can\'t display attribute names that contain these
    -- characters. This restriction doesn\'t apply to attribute values.
    EndpointBatchItem -> Maybe (HashMap Text [Text])
attributes :: Prelude.Maybe (Prelude.HashMap Prelude.Text [Prelude.Text]),
    -- | The channel to use when sending messages or push notifications to the
    -- endpoint.
    EndpointBatchItem -> Maybe ChannelType
channelType :: Prelude.Maybe ChannelType,
    -- | The demographic information for the endpoint, such as the time zone and
    -- platform.
    EndpointBatchItem -> Maybe EndpointDemographic
demographic :: Prelude.Maybe EndpointDemographic,
    -- | The date and time, in ISO 8601 format, when the endpoint was created or
    -- updated.
    EndpointBatchItem -> Maybe Text
effectiveDate :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether to send messages or push notifications to the
    -- endpoint. Valid values are: ACTIVE, messages are sent to the endpoint;
    -- and, INACTIVE, messages aren’t sent to the endpoint.
    --
    -- Amazon Pinpoint automatically sets this value to ACTIVE when you create
    -- an endpoint or update an existing endpoint. Amazon Pinpoint
    -- automatically sets this value to INACTIVE if you update another endpoint
    -- that has the same address specified by the Address property.
    EndpointBatchItem -> Maybe Text
endpointStatus :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier for the endpoint in the context of the batch.
    EndpointBatchItem -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The geographic information for the endpoint.
    EndpointBatchItem -> Maybe EndpointLocation
location :: Prelude.Maybe EndpointLocation,
    -- | One or more custom metrics that your app reports to Amazon Pinpoint for
    -- the endpoint.
    EndpointBatchItem -> Maybe (HashMap Text Double)
metrics :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Double),
    -- | Specifies whether the user who\'s associated with the endpoint has opted
    -- out of receiving messages and push notifications from you. Possible
    -- values are: ALL, the user has opted out and doesn\'t want to receive any
    -- messages or push notifications; and, NONE, the user hasn\'t opted out
    -- and wants to receive all messages and push notifications.
    EndpointBatchItem -> Maybe Text
optOut :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier for the request to create or update the endpoint.
    EndpointBatchItem -> Maybe Text
requestId :: Prelude.Maybe Prelude.Text,
    -- | One or more custom attributes that describe the user who\'s associated
    -- with the endpoint.
    EndpointBatchItem -> Maybe EndpointUser
user :: Prelude.Maybe EndpointUser
  }
  deriving (EndpointBatchItem -> EndpointBatchItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EndpointBatchItem -> EndpointBatchItem -> Bool
$c/= :: EndpointBatchItem -> EndpointBatchItem -> Bool
== :: EndpointBatchItem -> EndpointBatchItem -> Bool
$c== :: EndpointBatchItem -> EndpointBatchItem -> Bool
Prelude.Eq, ReadPrec [EndpointBatchItem]
ReadPrec EndpointBatchItem
Int -> ReadS EndpointBatchItem
ReadS [EndpointBatchItem]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EndpointBatchItem]
$creadListPrec :: ReadPrec [EndpointBatchItem]
readPrec :: ReadPrec EndpointBatchItem
$creadPrec :: ReadPrec EndpointBatchItem
readList :: ReadS [EndpointBatchItem]
$creadList :: ReadS [EndpointBatchItem]
readsPrec :: Int -> ReadS EndpointBatchItem
$creadsPrec :: Int -> ReadS EndpointBatchItem
Prelude.Read, Int -> EndpointBatchItem -> ShowS
[EndpointBatchItem] -> ShowS
EndpointBatchItem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EndpointBatchItem] -> ShowS
$cshowList :: [EndpointBatchItem] -> ShowS
show :: EndpointBatchItem -> String
$cshow :: EndpointBatchItem -> String
showsPrec :: Int -> EndpointBatchItem -> ShowS
$cshowsPrec :: Int -> EndpointBatchItem -> ShowS
Prelude.Show, forall x. Rep EndpointBatchItem x -> EndpointBatchItem
forall x. EndpointBatchItem -> Rep EndpointBatchItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EndpointBatchItem x -> EndpointBatchItem
$cfrom :: forall x. EndpointBatchItem -> Rep EndpointBatchItem x
Prelude.Generic)

-- |
-- Create a value of 'EndpointBatchItem' 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', 'endpointBatchItem_address' - The destination address for messages or push notifications that you send
-- to the endpoint. The address varies by channel. For a push-notification
-- channel, use the token provided by the push notification service, such
-- as an Apple Push Notification service (APNs) device token or a Firebase
-- Cloud Messaging (FCM) registration token. For the SMS channel, use a
-- phone number in E.164 format, such as +12065550100. For the email
-- channel, use an email address.
--
-- 'attributes', 'endpointBatchItem_attributes' - One or more custom attributes that describe the endpoint by associating
-- a name with an array of values. For example, the value of a custom
-- attribute named Interests might be: [\"Science\", \"Music\",
-- \"Travel\"]. You can use these attributes as filter criteria when you
-- create segments. Attribute names are case sensitive.
--
-- An attribute name can contain up to 50 characters. An attribute value
-- can contain up to 100 characters. When you define the name of a custom
-- attribute, avoid using the following characters: number sign (#), colon
-- (:), question mark (?), backslash (\\), and slash (\/). The Amazon
-- Pinpoint console can\'t display attribute names that contain these
-- characters. This restriction doesn\'t apply to attribute values.
--
-- 'channelType', 'endpointBatchItem_channelType' - The channel to use when sending messages or push notifications to the
-- endpoint.
--
-- 'demographic', 'endpointBatchItem_demographic' - The demographic information for the endpoint, such as the time zone and
-- platform.
--
-- 'effectiveDate', 'endpointBatchItem_effectiveDate' - The date and time, in ISO 8601 format, when the endpoint was created or
-- updated.
--
-- 'endpointStatus', 'endpointBatchItem_endpointStatus' - Specifies whether to send messages or push notifications to the
-- endpoint. Valid values are: ACTIVE, messages are sent to the endpoint;
-- and, INACTIVE, messages aren’t sent to the endpoint.
--
-- Amazon Pinpoint automatically sets this value to ACTIVE when you create
-- an endpoint or update an existing endpoint. Amazon Pinpoint
-- automatically sets this value to INACTIVE if you update another endpoint
-- that has the same address specified by the Address property.
--
-- 'id', 'endpointBatchItem_id' - The unique identifier for the endpoint in the context of the batch.
--
-- 'location', 'endpointBatchItem_location' - The geographic information for the endpoint.
--
-- 'metrics', 'endpointBatchItem_metrics' - One or more custom metrics that your app reports to Amazon Pinpoint for
-- the endpoint.
--
-- 'optOut', 'endpointBatchItem_optOut' - Specifies whether the user who\'s associated with the endpoint has opted
-- out of receiving messages and push notifications from you. Possible
-- values are: ALL, the user has opted out and doesn\'t want to receive any
-- messages or push notifications; and, NONE, the user hasn\'t opted out
-- and wants to receive all messages and push notifications.
--
-- 'requestId', 'endpointBatchItem_requestId' - The unique identifier for the request to create or update the endpoint.
--
-- 'user', 'endpointBatchItem_user' - One or more custom attributes that describe the user who\'s associated
-- with the endpoint.
newEndpointBatchItem ::
  EndpointBatchItem
newEndpointBatchItem :: EndpointBatchItem
newEndpointBatchItem =
  EndpointBatchItem'
    { $sel:address:EndpointBatchItem' :: Maybe Text
address = forall a. Maybe a
Prelude.Nothing,
      $sel:attributes:EndpointBatchItem' :: Maybe (HashMap Text [Text])
attributes = forall a. Maybe a
Prelude.Nothing,
      $sel:channelType:EndpointBatchItem' :: Maybe ChannelType
channelType = forall a. Maybe a
Prelude.Nothing,
      $sel:demographic:EndpointBatchItem' :: Maybe EndpointDemographic
demographic = forall a. Maybe a
Prelude.Nothing,
      $sel:effectiveDate:EndpointBatchItem' :: Maybe Text
effectiveDate = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointStatus:EndpointBatchItem' :: Maybe Text
endpointStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:id:EndpointBatchItem' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:location:EndpointBatchItem' :: Maybe EndpointLocation
location = forall a. Maybe a
Prelude.Nothing,
      $sel:metrics:EndpointBatchItem' :: Maybe (HashMap Text Double)
metrics = forall a. Maybe a
Prelude.Nothing,
      $sel:optOut:EndpointBatchItem' :: Maybe Text
optOut = forall a. Maybe a
Prelude.Nothing,
      $sel:requestId:EndpointBatchItem' :: Maybe Text
requestId = forall a. Maybe a
Prelude.Nothing,
      $sel:user:EndpointBatchItem' :: Maybe EndpointUser
user = forall a. Maybe a
Prelude.Nothing
    }

-- | The destination address for messages or push notifications that you send
-- to the endpoint. The address varies by channel. For a push-notification
-- channel, use the token provided by the push notification service, such
-- as an Apple Push Notification service (APNs) device token or a Firebase
-- Cloud Messaging (FCM) registration token. For the SMS channel, use a
-- phone number in E.164 format, such as +12065550100. For the email
-- channel, use an email address.
endpointBatchItem_address :: Lens.Lens' EndpointBatchItem (Prelude.Maybe Prelude.Text)
endpointBatchItem_address :: Lens' EndpointBatchItem (Maybe Text)
endpointBatchItem_address = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EndpointBatchItem' {Maybe Text
address :: Maybe Text
$sel:address:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
address} -> Maybe Text
address) (\s :: EndpointBatchItem
s@EndpointBatchItem' {} Maybe Text
a -> EndpointBatchItem
s {$sel:address:EndpointBatchItem' :: Maybe Text
address = Maybe Text
a} :: EndpointBatchItem)

-- | One or more custom attributes that describe the endpoint by associating
-- a name with an array of values. For example, the value of a custom
-- attribute named Interests might be: [\"Science\", \"Music\",
-- \"Travel\"]. You can use these attributes as filter criteria when you
-- create segments. Attribute names are case sensitive.
--
-- An attribute name can contain up to 50 characters. An attribute value
-- can contain up to 100 characters. When you define the name of a custom
-- attribute, avoid using the following characters: number sign (#), colon
-- (:), question mark (?), backslash (\\), and slash (\/). The Amazon
-- Pinpoint console can\'t display attribute names that contain these
-- characters. This restriction doesn\'t apply to attribute values.
endpointBatchItem_attributes :: Lens.Lens' EndpointBatchItem (Prelude.Maybe (Prelude.HashMap Prelude.Text [Prelude.Text]))
endpointBatchItem_attributes :: Lens' EndpointBatchItem (Maybe (HashMap Text [Text]))
endpointBatchItem_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EndpointBatchItem' {Maybe (HashMap Text [Text])
attributes :: Maybe (HashMap Text [Text])
$sel:attributes:EndpointBatchItem' :: EndpointBatchItem -> Maybe (HashMap Text [Text])
attributes} -> Maybe (HashMap Text [Text])
attributes) (\s :: EndpointBatchItem
s@EndpointBatchItem' {} Maybe (HashMap Text [Text])
a -> EndpointBatchItem
s {$sel:attributes:EndpointBatchItem' :: Maybe (HashMap Text [Text])
attributes = Maybe (HashMap Text [Text])
a} :: EndpointBatchItem) 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 channel to use when sending messages or push notifications to the
-- endpoint.
endpointBatchItem_channelType :: Lens.Lens' EndpointBatchItem (Prelude.Maybe ChannelType)
endpointBatchItem_channelType :: Lens' EndpointBatchItem (Maybe ChannelType)
endpointBatchItem_channelType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EndpointBatchItem' {Maybe ChannelType
channelType :: Maybe ChannelType
$sel:channelType:EndpointBatchItem' :: EndpointBatchItem -> Maybe ChannelType
channelType} -> Maybe ChannelType
channelType) (\s :: EndpointBatchItem
s@EndpointBatchItem' {} Maybe ChannelType
a -> EndpointBatchItem
s {$sel:channelType:EndpointBatchItem' :: Maybe ChannelType
channelType = Maybe ChannelType
a} :: EndpointBatchItem)

-- | The demographic information for the endpoint, such as the time zone and
-- platform.
endpointBatchItem_demographic :: Lens.Lens' EndpointBatchItem (Prelude.Maybe EndpointDemographic)
endpointBatchItem_demographic :: Lens' EndpointBatchItem (Maybe EndpointDemographic)
endpointBatchItem_demographic = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EndpointBatchItem' {Maybe EndpointDemographic
demographic :: Maybe EndpointDemographic
$sel:demographic:EndpointBatchItem' :: EndpointBatchItem -> Maybe EndpointDemographic
demographic} -> Maybe EndpointDemographic
demographic) (\s :: EndpointBatchItem
s@EndpointBatchItem' {} Maybe EndpointDemographic
a -> EndpointBatchItem
s {$sel:demographic:EndpointBatchItem' :: Maybe EndpointDemographic
demographic = Maybe EndpointDemographic
a} :: EndpointBatchItem)

-- | The date and time, in ISO 8601 format, when the endpoint was created or
-- updated.
endpointBatchItem_effectiveDate :: Lens.Lens' EndpointBatchItem (Prelude.Maybe Prelude.Text)
endpointBatchItem_effectiveDate :: Lens' EndpointBatchItem (Maybe Text)
endpointBatchItem_effectiveDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EndpointBatchItem' {Maybe Text
effectiveDate :: Maybe Text
$sel:effectiveDate:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
effectiveDate} -> Maybe Text
effectiveDate) (\s :: EndpointBatchItem
s@EndpointBatchItem' {} Maybe Text
a -> EndpointBatchItem
s {$sel:effectiveDate:EndpointBatchItem' :: Maybe Text
effectiveDate = Maybe Text
a} :: EndpointBatchItem)

-- | Specifies whether to send messages or push notifications to the
-- endpoint. Valid values are: ACTIVE, messages are sent to the endpoint;
-- and, INACTIVE, messages aren’t sent to the endpoint.
--
-- Amazon Pinpoint automatically sets this value to ACTIVE when you create
-- an endpoint or update an existing endpoint. Amazon Pinpoint
-- automatically sets this value to INACTIVE if you update another endpoint
-- that has the same address specified by the Address property.
endpointBatchItem_endpointStatus :: Lens.Lens' EndpointBatchItem (Prelude.Maybe Prelude.Text)
endpointBatchItem_endpointStatus :: Lens' EndpointBatchItem (Maybe Text)
endpointBatchItem_endpointStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EndpointBatchItem' {Maybe Text
endpointStatus :: Maybe Text
$sel:endpointStatus:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
endpointStatus} -> Maybe Text
endpointStatus) (\s :: EndpointBatchItem
s@EndpointBatchItem' {} Maybe Text
a -> EndpointBatchItem
s {$sel:endpointStatus:EndpointBatchItem' :: Maybe Text
endpointStatus = Maybe Text
a} :: EndpointBatchItem)

-- | The unique identifier for the endpoint in the context of the batch.
endpointBatchItem_id :: Lens.Lens' EndpointBatchItem (Prelude.Maybe Prelude.Text)
endpointBatchItem_id :: Lens' EndpointBatchItem (Maybe Text)
endpointBatchItem_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EndpointBatchItem' {Maybe Text
id :: Maybe Text
$sel:id:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
id} -> Maybe Text
id) (\s :: EndpointBatchItem
s@EndpointBatchItem' {} Maybe Text
a -> EndpointBatchItem
s {$sel:id:EndpointBatchItem' :: Maybe Text
id = Maybe Text
a} :: EndpointBatchItem)

-- | The geographic information for the endpoint.
endpointBatchItem_location :: Lens.Lens' EndpointBatchItem (Prelude.Maybe EndpointLocation)
endpointBatchItem_location :: Lens' EndpointBatchItem (Maybe EndpointLocation)
endpointBatchItem_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EndpointBatchItem' {Maybe EndpointLocation
location :: Maybe EndpointLocation
$sel:location:EndpointBatchItem' :: EndpointBatchItem -> Maybe EndpointLocation
location} -> Maybe EndpointLocation
location) (\s :: EndpointBatchItem
s@EndpointBatchItem' {} Maybe EndpointLocation
a -> EndpointBatchItem
s {$sel:location:EndpointBatchItem' :: Maybe EndpointLocation
location = Maybe EndpointLocation
a} :: EndpointBatchItem)

-- | One or more custom metrics that your app reports to Amazon Pinpoint for
-- the endpoint.
endpointBatchItem_metrics :: Lens.Lens' EndpointBatchItem (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Double))
endpointBatchItem_metrics :: Lens' EndpointBatchItem (Maybe (HashMap Text Double))
endpointBatchItem_metrics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EndpointBatchItem' {Maybe (HashMap Text Double)
metrics :: Maybe (HashMap Text Double)
$sel:metrics:EndpointBatchItem' :: EndpointBatchItem -> Maybe (HashMap Text Double)
metrics} -> Maybe (HashMap Text Double)
metrics) (\s :: EndpointBatchItem
s@EndpointBatchItem' {} Maybe (HashMap Text Double)
a -> EndpointBatchItem
s {$sel:metrics:EndpointBatchItem' :: Maybe (HashMap Text Double)
metrics = Maybe (HashMap Text Double)
a} :: EndpointBatchItem) 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

-- | Specifies whether the user who\'s associated with the endpoint has opted
-- out of receiving messages and push notifications from you. Possible
-- values are: ALL, the user has opted out and doesn\'t want to receive any
-- messages or push notifications; and, NONE, the user hasn\'t opted out
-- and wants to receive all messages and push notifications.
endpointBatchItem_optOut :: Lens.Lens' EndpointBatchItem (Prelude.Maybe Prelude.Text)
endpointBatchItem_optOut :: Lens' EndpointBatchItem (Maybe Text)
endpointBatchItem_optOut = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EndpointBatchItem' {Maybe Text
optOut :: Maybe Text
$sel:optOut:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
optOut} -> Maybe Text
optOut) (\s :: EndpointBatchItem
s@EndpointBatchItem' {} Maybe Text
a -> EndpointBatchItem
s {$sel:optOut:EndpointBatchItem' :: Maybe Text
optOut = Maybe Text
a} :: EndpointBatchItem)

-- | The unique identifier for the request to create or update the endpoint.
endpointBatchItem_requestId :: Lens.Lens' EndpointBatchItem (Prelude.Maybe Prelude.Text)
endpointBatchItem_requestId :: Lens' EndpointBatchItem (Maybe Text)
endpointBatchItem_requestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EndpointBatchItem' {Maybe Text
requestId :: Maybe Text
$sel:requestId:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
requestId} -> Maybe Text
requestId) (\s :: EndpointBatchItem
s@EndpointBatchItem' {} Maybe Text
a -> EndpointBatchItem
s {$sel:requestId:EndpointBatchItem' :: Maybe Text
requestId = Maybe Text
a} :: EndpointBatchItem)

-- | One or more custom attributes that describe the user who\'s associated
-- with the endpoint.
endpointBatchItem_user :: Lens.Lens' EndpointBatchItem (Prelude.Maybe EndpointUser)
endpointBatchItem_user :: Lens' EndpointBatchItem (Maybe EndpointUser)
endpointBatchItem_user = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EndpointBatchItem' {Maybe EndpointUser
user :: Maybe EndpointUser
$sel:user:EndpointBatchItem' :: EndpointBatchItem -> Maybe EndpointUser
user} -> Maybe EndpointUser
user) (\s :: EndpointBatchItem
s@EndpointBatchItem' {} Maybe EndpointUser
a -> EndpointBatchItem
s {$sel:user:EndpointBatchItem' :: Maybe EndpointUser
user = Maybe EndpointUser
a} :: EndpointBatchItem)

instance Prelude.Hashable EndpointBatchItem where
  hashWithSalt :: Int -> EndpointBatchItem -> Int
hashWithSalt Int
_salt EndpointBatchItem' {Maybe Text
Maybe (HashMap Text Double)
Maybe (HashMap Text [Text])
Maybe ChannelType
Maybe EndpointDemographic
Maybe EndpointLocation
Maybe EndpointUser
user :: Maybe EndpointUser
requestId :: Maybe Text
optOut :: Maybe Text
metrics :: Maybe (HashMap Text Double)
location :: Maybe EndpointLocation
id :: Maybe Text
endpointStatus :: Maybe Text
effectiveDate :: Maybe Text
demographic :: Maybe EndpointDemographic
channelType :: Maybe ChannelType
attributes :: Maybe (HashMap Text [Text])
address :: Maybe Text
$sel:user:EndpointBatchItem' :: EndpointBatchItem -> Maybe EndpointUser
$sel:requestId:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:optOut:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:metrics:EndpointBatchItem' :: EndpointBatchItem -> Maybe (HashMap Text Double)
$sel:location:EndpointBatchItem' :: EndpointBatchItem -> Maybe EndpointLocation
$sel:id:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:endpointStatus:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:effectiveDate:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:demographic:EndpointBatchItem' :: EndpointBatchItem -> Maybe EndpointDemographic
$sel:channelType:EndpointBatchItem' :: EndpointBatchItem -> Maybe ChannelType
$sel:attributes:EndpointBatchItem' :: EndpointBatchItem -> Maybe (HashMap Text [Text])
$sel:address:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
..} =
    Int
_salt
      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 ChannelType
channelType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EndpointDemographic
demographic
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
effectiveDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
endpointStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EndpointLocation
location
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Double)
metrics
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
optOut
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
requestId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EndpointUser
user

instance Prelude.NFData EndpointBatchItem where
  rnf :: EndpointBatchItem -> ()
rnf EndpointBatchItem' {Maybe Text
Maybe (HashMap Text Double)
Maybe (HashMap Text [Text])
Maybe ChannelType
Maybe EndpointDemographic
Maybe EndpointLocation
Maybe EndpointUser
user :: Maybe EndpointUser
requestId :: Maybe Text
optOut :: Maybe Text
metrics :: Maybe (HashMap Text Double)
location :: Maybe EndpointLocation
id :: Maybe Text
endpointStatus :: Maybe Text
effectiveDate :: Maybe Text
demographic :: Maybe EndpointDemographic
channelType :: Maybe ChannelType
attributes :: Maybe (HashMap Text [Text])
address :: Maybe Text
$sel:user:EndpointBatchItem' :: EndpointBatchItem -> Maybe EndpointUser
$sel:requestId:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:optOut:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:metrics:EndpointBatchItem' :: EndpointBatchItem -> Maybe (HashMap Text Double)
$sel:location:EndpointBatchItem' :: EndpointBatchItem -> Maybe EndpointLocation
$sel:id:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:endpointStatus:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:effectiveDate:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:demographic:EndpointBatchItem' :: EndpointBatchItem -> Maybe EndpointDemographic
$sel:channelType:EndpointBatchItem' :: EndpointBatchItem -> Maybe ChannelType
$sel:attributes:EndpointBatchItem' :: EndpointBatchItem -> Maybe (HashMap Text [Text])
$sel:address:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
..} =
    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 ChannelType
channelType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EndpointDemographic
demographic
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
effectiveDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
endpointStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EndpointLocation
location
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Double)
metrics
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
optOut
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
requestId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EndpointUser
user

instance Data.ToJSON EndpointBatchItem where
  toJSON :: EndpointBatchItem -> Value
toJSON EndpointBatchItem' {Maybe Text
Maybe (HashMap Text Double)
Maybe (HashMap Text [Text])
Maybe ChannelType
Maybe EndpointDemographic
Maybe EndpointLocation
Maybe EndpointUser
user :: Maybe EndpointUser
requestId :: Maybe Text
optOut :: Maybe Text
metrics :: Maybe (HashMap Text Double)
location :: Maybe EndpointLocation
id :: Maybe Text
endpointStatus :: Maybe Text
effectiveDate :: Maybe Text
demographic :: Maybe EndpointDemographic
channelType :: Maybe ChannelType
attributes :: Maybe (HashMap Text [Text])
address :: Maybe Text
$sel:user:EndpointBatchItem' :: EndpointBatchItem -> Maybe EndpointUser
$sel:requestId:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:optOut:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:metrics:EndpointBatchItem' :: EndpointBatchItem -> Maybe (HashMap Text Double)
$sel:location:EndpointBatchItem' :: EndpointBatchItem -> Maybe EndpointLocation
$sel:id:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:endpointStatus:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:effectiveDate:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
$sel:demographic:EndpointBatchItem' :: EndpointBatchItem -> Maybe EndpointDemographic
$sel:channelType:EndpointBatchItem' :: EndpointBatchItem -> Maybe ChannelType
$sel:attributes:EndpointBatchItem' :: EndpointBatchItem -> Maybe (HashMap Text [Text])
$sel:address:EndpointBatchItem' :: EndpointBatchItem -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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
"ChannelType" 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 ChannelType
channelType,
            (Key
"Demographic" 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 EndpointDemographic
demographic,
            (Key
"EffectiveDate" 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
effectiveDate,
            (Key
"EndpointStatus" 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
endpointStatus,
            (Key
"Id" 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
id,
            (Key
"Location" 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 EndpointLocation
location,
            (Key
"Metrics" 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 Double)
metrics,
            (Key
"OptOut" 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
optOut,
            (Key
"RequestId" 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
requestId,
            (Key
"User" 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 EndpointUser
user
          ]
      )