{-# 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.PublicEndpoint
-- 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.PublicEndpoint 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 the properties and attributes of an endpoint that\'s
-- associated with an event.
--
-- /See:/ 'newPublicEndpoint' smart constructor.
data PublicEndpoint = PublicEndpoint'
  { -- | The unique identifier for the recipient, such as a device token, email
    -- address, or mobile phone number.
    PublicEndpoint -> 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. You can use these attributes as filter
    -- criteria when you create segments.
    PublicEndpoint -> Maybe (HashMap Text [Text])
attributes :: Prelude.Maybe (Prelude.HashMap Prelude.Text [Prelude.Text]),
    -- | The channel that\'s used when sending messages or push notifications to
    -- the endpoint.
    PublicEndpoint -> Maybe ChannelType
channelType :: Prelude.Maybe ChannelType,
    -- | The demographic information for the endpoint, such as the time zone and
    -- platform.
    PublicEndpoint -> Maybe EndpointDemographic
demographic :: Prelude.Maybe EndpointDemographic,
    -- | The date and time, in ISO 8601 format, when the endpoint was last
    -- updated.
    PublicEndpoint -> 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.
    PublicEndpoint -> Maybe Text
endpointStatus :: Prelude.Maybe Prelude.Text,
    -- | The geographic information for the endpoint.
    PublicEndpoint -> Maybe EndpointLocation
location :: Prelude.Maybe EndpointLocation,
    -- | One or more custom metrics that your app reports to Amazon Pinpoint for
    -- the endpoint.
    PublicEndpoint -> 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.
    PublicEndpoint -> Maybe Text
optOut :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier that\'s generated each time the endpoint is updated.
    PublicEndpoint -> Maybe Text
requestId :: Prelude.Maybe Prelude.Text,
    -- | One or more custom user attributes that your app reports to Amazon
    -- Pinpoint for the user who\'s associated with the endpoint.
    PublicEndpoint -> Maybe EndpointUser
user :: Prelude.Maybe EndpointUser
  }
  deriving (PublicEndpoint -> PublicEndpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublicEndpoint -> PublicEndpoint -> Bool
$c/= :: PublicEndpoint -> PublicEndpoint -> Bool
== :: PublicEndpoint -> PublicEndpoint -> Bool
$c== :: PublicEndpoint -> PublicEndpoint -> Bool
Prelude.Eq, ReadPrec [PublicEndpoint]
ReadPrec PublicEndpoint
Int -> ReadS PublicEndpoint
ReadS [PublicEndpoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PublicEndpoint]
$creadListPrec :: ReadPrec [PublicEndpoint]
readPrec :: ReadPrec PublicEndpoint
$creadPrec :: ReadPrec PublicEndpoint
readList :: ReadS [PublicEndpoint]
$creadList :: ReadS [PublicEndpoint]
readsPrec :: Int -> ReadS PublicEndpoint
$creadsPrec :: Int -> ReadS PublicEndpoint
Prelude.Read, Int -> PublicEndpoint -> ShowS
[PublicEndpoint] -> ShowS
PublicEndpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicEndpoint] -> ShowS
$cshowList :: [PublicEndpoint] -> ShowS
show :: PublicEndpoint -> String
$cshow :: PublicEndpoint -> String
showsPrec :: Int -> PublicEndpoint -> ShowS
$cshowsPrec :: Int -> PublicEndpoint -> ShowS
Prelude.Show, forall x. Rep PublicEndpoint x -> PublicEndpoint
forall x. PublicEndpoint -> Rep PublicEndpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PublicEndpoint x -> PublicEndpoint
$cfrom :: forall x. PublicEndpoint -> Rep PublicEndpoint x
Prelude.Generic)

-- |
-- Create a value of 'PublicEndpoint' 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', 'publicEndpoint_address' - The unique identifier for the recipient, such as a device token, email
-- address, or mobile phone number.
--
-- 'attributes', 'publicEndpoint_attributes' - One or more custom attributes that describe the endpoint by associating
-- a name with an array of values. You can use these attributes as filter
-- criteria when you create segments.
--
-- 'channelType', 'publicEndpoint_channelType' - The channel that\'s used when sending messages or push notifications to
-- the endpoint.
--
-- 'demographic', 'publicEndpoint_demographic' - The demographic information for the endpoint, such as the time zone and
-- platform.
--
-- 'effectiveDate', 'publicEndpoint_effectiveDate' - The date and time, in ISO 8601 format, when the endpoint was last
-- updated.
--
-- 'endpointStatus', 'publicEndpoint_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.
--
-- 'location', 'publicEndpoint_location' - The geographic information for the endpoint.
--
-- 'metrics', 'publicEndpoint_metrics' - One or more custom metrics that your app reports to Amazon Pinpoint for
-- the endpoint.
--
-- 'optOut', 'publicEndpoint_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', 'publicEndpoint_requestId' - A unique identifier that\'s generated each time the endpoint is updated.
--
-- 'user', 'publicEndpoint_user' - One or more custom user attributes that your app reports to Amazon
-- Pinpoint for the user who\'s associated with the endpoint.
newPublicEndpoint ::
  PublicEndpoint
newPublicEndpoint :: PublicEndpoint
newPublicEndpoint =
  PublicEndpoint'
    { $sel:address:PublicEndpoint' :: Maybe Text
address = forall a. Maybe a
Prelude.Nothing,
      $sel:attributes:PublicEndpoint' :: Maybe (HashMap Text [Text])
attributes = forall a. Maybe a
Prelude.Nothing,
      $sel:channelType:PublicEndpoint' :: Maybe ChannelType
channelType = forall a. Maybe a
Prelude.Nothing,
      $sel:demographic:PublicEndpoint' :: Maybe EndpointDemographic
demographic = forall a. Maybe a
Prelude.Nothing,
      $sel:effectiveDate:PublicEndpoint' :: Maybe Text
effectiveDate = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointStatus:PublicEndpoint' :: Maybe Text
endpointStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:location:PublicEndpoint' :: Maybe EndpointLocation
location = forall a. Maybe a
Prelude.Nothing,
      $sel:metrics:PublicEndpoint' :: Maybe (HashMap Text Double)
metrics = forall a. Maybe a
Prelude.Nothing,
      $sel:optOut:PublicEndpoint' :: Maybe Text
optOut = forall a. Maybe a
Prelude.Nothing,
      $sel:requestId:PublicEndpoint' :: Maybe Text
requestId = forall a. Maybe a
Prelude.Nothing,
      $sel:user:PublicEndpoint' :: Maybe EndpointUser
user = forall a. Maybe a
Prelude.Nothing
    }

-- | The unique identifier for the recipient, such as a device token, email
-- address, or mobile phone number.
publicEndpoint_address :: Lens.Lens' PublicEndpoint (Prelude.Maybe Prelude.Text)
publicEndpoint_address :: Lens' PublicEndpoint (Maybe Text)
publicEndpoint_address = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublicEndpoint' {Maybe Text
address :: Maybe Text
$sel:address:PublicEndpoint' :: PublicEndpoint -> Maybe Text
address} -> Maybe Text
address) (\s :: PublicEndpoint
s@PublicEndpoint' {} Maybe Text
a -> PublicEndpoint
s {$sel:address:PublicEndpoint' :: Maybe Text
address = Maybe Text
a} :: PublicEndpoint)

-- | One or more custom attributes that describe the endpoint by associating
-- a name with an array of values. You can use these attributes as filter
-- criteria when you create segments.
publicEndpoint_attributes :: Lens.Lens' PublicEndpoint (Prelude.Maybe (Prelude.HashMap Prelude.Text [Prelude.Text]))
publicEndpoint_attributes :: Lens' PublicEndpoint (Maybe (HashMap Text [Text]))
publicEndpoint_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublicEndpoint' {Maybe (HashMap Text [Text])
attributes :: Maybe (HashMap Text [Text])
$sel:attributes:PublicEndpoint' :: PublicEndpoint -> Maybe (HashMap Text [Text])
attributes} -> Maybe (HashMap Text [Text])
attributes) (\s :: PublicEndpoint
s@PublicEndpoint' {} Maybe (HashMap Text [Text])
a -> PublicEndpoint
s {$sel:attributes:PublicEndpoint' :: Maybe (HashMap Text [Text])
attributes = Maybe (HashMap Text [Text])
a} :: PublicEndpoint) 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 that\'s used when sending messages or push notifications to
-- the endpoint.
publicEndpoint_channelType :: Lens.Lens' PublicEndpoint (Prelude.Maybe ChannelType)
publicEndpoint_channelType :: Lens' PublicEndpoint (Maybe ChannelType)
publicEndpoint_channelType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublicEndpoint' {Maybe ChannelType
channelType :: Maybe ChannelType
$sel:channelType:PublicEndpoint' :: PublicEndpoint -> Maybe ChannelType
channelType} -> Maybe ChannelType
channelType) (\s :: PublicEndpoint
s@PublicEndpoint' {} Maybe ChannelType
a -> PublicEndpoint
s {$sel:channelType:PublicEndpoint' :: Maybe ChannelType
channelType = Maybe ChannelType
a} :: PublicEndpoint)

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

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

-- | 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.
publicEndpoint_endpointStatus :: Lens.Lens' PublicEndpoint (Prelude.Maybe Prelude.Text)
publicEndpoint_endpointStatus :: Lens' PublicEndpoint (Maybe Text)
publicEndpoint_endpointStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublicEndpoint' {Maybe Text
endpointStatus :: Maybe Text
$sel:endpointStatus:PublicEndpoint' :: PublicEndpoint -> Maybe Text
endpointStatus} -> Maybe Text
endpointStatus) (\s :: PublicEndpoint
s@PublicEndpoint' {} Maybe Text
a -> PublicEndpoint
s {$sel:endpointStatus:PublicEndpoint' :: Maybe Text
endpointStatus = Maybe Text
a} :: PublicEndpoint)

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

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

-- | A unique identifier that\'s generated each time the endpoint is updated.
publicEndpoint_requestId :: Lens.Lens' PublicEndpoint (Prelude.Maybe Prelude.Text)
publicEndpoint_requestId :: Lens' PublicEndpoint (Maybe Text)
publicEndpoint_requestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublicEndpoint' {Maybe Text
requestId :: Maybe Text
$sel:requestId:PublicEndpoint' :: PublicEndpoint -> Maybe Text
requestId} -> Maybe Text
requestId) (\s :: PublicEndpoint
s@PublicEndpoint' {} Maybe Text
a -> PublicEndpoint
s {$sel:requestId:PublicEndpoint' :: Maybe Text
requestId = Maybe Text
a} :: PublicEndpoint)

-- | One or more custom user attributes that your app reports to Amazon
-- Pinpoint for the user who\'s associated with the endpoint.
publicEndpoint_user :: Lens.Lens' PublicEndpoint (Prelude.Maybe EndpointUser)
publicEndpoint_user :: Lens' PublicEndpoint (Maybe EndpointUser)
publicEndpoint_user = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublicEndpoint' {Maybe EndpointUser
user :: Maybe EndpointUser
$sel:user:PublicEndpoint' :: PublicEndpoint -> Maybe EndpointUser
user} -> Maybe EndpointUser
user) (\s :: PublicEndpoint
s@PublicEndpoint' {} Maybe EndpointUser
a -> PublicEndpoint
s {$sel:user:PublicEndpoint' :: Maybe EndpointUser
user = Maybe EndpointUser
a} :: PublicEndpoint)

instance Prelude.Hashable PublicEndpoint where
  hashWithSalt :: Int -> PublicEndpoint -> Int
hashWithSalt Int
_salt PublicEndpoint' {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
endpointStatus :: Maybe Text
effectiveDate :: Maybe Text
demographic :: Maybe EndpointDemographic
channelType :: Maybe ChannelType
attributes :: Maybe (HashMap Text [Text])
address :: Maybe Text
$sel:user:PublicEndpoint' :: PublicEndpoint -> Maybe EndpointUser
$sel:requestId:PublicEndpoint' :: PublicEndpoint -> Maybe Text
$sel:optOut:PublicEndpoint' :: PublicEndpoint -> Maybe Text
$sel:metrics:PublicEndpoint' :: PublicEndpoint -> Maybe (HashMap Text Double)
$sel:location:PublicEndpoint' :: PublicEndpoint -> Maybe EndpointLocation
$sel:endpointStatus:PublicEndpoint' :: PublicEndpoint -> Maybe Text
$sel:effectiveDate:PublicEndpoint' :: PublicEndpoint -> Maybe Text
$sel:demographic:PublicEndpoint' :: PublicEndpoint -> Maybe EndpointDemographic
$sel:channelType:PublicEndpoint' :: PublicEndpoint -> Maybe ChannelType
$sel:attributes:PublicEndpoint' :: PublicEndpoint -> Maybe (HashMap Text [Text])
$sel:address:PublicEndpoint' :: PublicEndpoint -> 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 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 PublicEndpoint where
  rnf :: PublicEndpoint -> ()
rnf PublicEndpoint' {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
endpointStatus :: Maybe Text
effectiveDate :: Maybe Text
demographic :: Maybe EndpointDemographic
channelType :: Maybe ChannelType
attributes :: Maybe (HashMap Text [Text])
address :: Maybe Text
$sel:user:PublicEndpoint' :: PublicEndpoint -> Maybe EndpointUser
$sel:requestId:PublicEndpoint' :: PublicEndpoint -> Maybe Text
$sel:optOut:PublicEndpoint' :: PublicEndpoint -> Maybe Text
$sel:metrics:PublicEndpoint' :: PublicEndpoint -> Maybe (HashMap Text Double)
$sel:location:PublicEndpoint' :: PublicEndpoint -> Maybe EndpointLocation
$sel:endpointStatus:PublicEndpoint' :: PublicEndpoint -> Maybe Text
$sel:effectiveDate:PublicEndpoint' :: PublicEndpoint -> Maybe Text
$sel:demographic:PublicEndpoint' :: PublicEndpoint -> Maybe EndpointDemographic
$sel:channelType:PublicEndpoint' :: PublicEndpoint -> Maybe ChannelType
$sel:attributes:PublicEndpoint' :: PublicEndpoint -> Maybe (HashMap Text [Text])
$sel:address:PublicEndpoint' :: PublicEndpoint -> 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 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 PublicEndpoint where
  toJSON :: PublicEndpoint -> Value
toJSON PublicEndpoint' {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
endpointStatus :: Maybe Text
effectiveDate :: Maybe Text
demographic :: Maybe EndpointDemographic
channelType :: Maybe ChannelType
attributes :: Maybe (HashMap Text [Text])
address :: Maybe Text
$sel:user:PublicEndpoint' :: PublicEndpoint -> Maybe EndpointUser
$sel:requestId:PublicEndpoint' :: PublicEndpoint -> Maybe Text
$sel:optOut:PublicEndpoint' :: PublicEndpoint -> Maybe Text
$sel:metrics:PublicEndpoint' :: PublicEndpoint -> Maybe (HashMap Text Double)
$sel:location:PublicEndpoint' :: PublicEndpoint -> Maybe EndpointLocation
$sel:endpointStatus:PublicEndpoint' :: PublicEndpoint -> Maybe Text
$sel:effectiveDate:PublicEndpoint' :: PublicEndpoint -> Maybe Text
$sel:demographic:PublicEndpoint' :: PublicEndpoint -> Maybe EndpointDemographic
$sel:channelType:PublicEndpoint' :: PublicEndpoint -> Maybe ChannelType
$sel:attributes:PublicEndpoint' :: PublicEndpoint -> Maybe (HashMap Text [Text])
$sel:address:PublicEndpoint' :: PublicEndpoint -> 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
"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
          ]
      )