{-# 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.CampaignResponse
-- 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.CampaignResponse 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.CampaignHook
import Amazonka.Pinpoint.Types.CampaignLimits
import Amazonka.Pinpoint.Types.CampaignState
import Amazonka.Pinpoint.Types.CustomDeliveryConfiguration
import Amazonka.Pinpoint.Types.MessageConfiguration
import Amazonka.Pinpoint.Types.Schedule
import Amazonka.Pinpoint.Types.TemplateConfiguration
import Amazonka.Pinpoint.Types.TreatmentResource
import qualified Amazonka.Prelude as Prelude

-- | Provides information about the status, configuration, and other settings
-- for a campaign.
--
-- /See:/ 'newCampaignResponse' smart constructor.
data CampaignResponse = CampaignResponse'
  { -- | An array of responses, one for each treatment that you defined for the
    -- campaign, in addition to the default treatment.
    CampaignResponse -> Maybe [TreatmentResource]
additionalTreatments :: Prelude.Maybe [TreatmentResource],
    -- | The delivery configuration settings for sending the campaign through a
    -- custom channel.
    CampaignResponse -> Maybe CustomDeliveryConfiguration
customDeliveryConfiguration :: Prelude.Maybe CustomDeliveryConfiguration,
    -- | The current status of the campaign\'s default treatment. This value
    -- exists only for campaigns that have more than one treatment.
    CampaignResponse -> Maybe CampaignState
defaultState :: Prelude.Maybe CampaignState,
    -- | The custom description of the campaign.
    CampaignResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The allocated percentage of users (segment members) who shouldn\'t
    -- receive messages from the campaign.
    CampaignResponse -> Maybe Int
holdoutPercent :: Prelude.Maybe Prelude.Int,
    -- | The settings for the AWS Lambda function to use as a code hook for the
    -- campaign. You can use this hook to customize the segment that\'s used by
    -- the campaign.
    CampaignResponse -> Maybe CampaignHook
hook :: Prelude.Maybe CampaignHook,
    -- | Specifies whether the campaign is paused. A paused campaign doesn\'t run
    -- unless you resume it by changing this value to false.
    CampaignResponse -> Maybe Bool
isPaused :: Prelude.Maybe Prelude.Bool,
    -- | The messaging limits for the campaign.
    CampaignResponse -> Maybe CampaignLimits
limits :: Prelude.Maybe CampaignLimits,
    -- | The message configuration settings for the campaign.
    CampaignResponse -> Maybe MessageConfiguration
messageConfiguration :: Prelude.Maybe MessageConfiguration,
    -- | The name of the campaign.
    CampaignResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Defines the priority of the campaign, used to decide the order of
    -- messages displayed to user if there are multiple messages scheduled to
    -- be displayed at the same moment.
    CampaignResponse -> Maybe Int
priority :: Prelude.Maybe Prelude.Int,
    -- | The schedule settings for the campaign.
    CampaignResponse -> Maybe Schedule
schedule :: Prelude.Maybe Schedule,
    -- | The current status of the campaign.
    CampaignResponse -> Maybe CampaignState
state :: Prelude.Maybe CampaignState,
    -- | The message template that’s used for the campaign.
    CampaignResponse -> Maybe TemplateConfiguration
templateConfiguration :: Prelude.Maybe TemplateConfiguration,
    -- | The custom description of the default treatment for the campaign.
    CampaignResponse -> Maybe Text
treatmentDescription :: Prelude.Maybe Prelude.Text,
    -- | The custom name of the default treatment for the campaign, if the
    -- campaign has multiple treatments. A /treatment/ is a variation of a
    -- campaign that\'s used for A\/B testing.
    CampaignResponse -> Maybe Text
treatmentName :: Prelude.Maybe Prelude.Text,
    -- | The version number of the campaign.
    CampaignResponse -> Maybe Int
version :: Prelude.Maybe Prelude.Int,
    -- | A string-to-string map of key-value pairs that identifies the tags that
    -- are associated with the campaign. Each tag consists of a required tag
    -- key and an associated tag value.
    CampaignResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The date, in ISO 8601 format, when the campaign was last modified.
    CampaignResponse -> Text
lastModifiedDate :: Prelude.Text,
    -- | The date, in ISO 8601 format, when the campaign was created.
    CampaignResponse -> Text
creationDate :: Prelude.Text,
    -- | The unique identifier for the segment that\'s associated with the
    -- campaign.
    CampaignResponse -> Text
segmentId :: Prelude.Text,
    -- | The version number of the segment that\'s associated with the campaign.
    CampaignResponse -> Int
segmentVersion :: Prelude.Int,
    -- | The unique identifier for the campaign.
    CampaignResponse -> Text
id :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the campaign.
    CampaignResponse -> Text
arn :: Prelude.Text,
    -- | The unique identifier for the application that the campaign applies to.
    CampaignResponse -> Text
applicationId :: Prelude.Text
  }
  deriving (CampaignResponse -> CampaignResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CampaignResponse -> CampaignResponse -> Bool
$c/= :: CampaignResponse -> CampaignResponse -> Bool
== :: CampaignResponse -> CampaignResponse -> Bool
$c== :: CampaignResponse -> CampaignResponse -> Bool
Prelude.Eq, ReadPrec [CampaignResponse]
ReadPrec CampaignResponse
Int -> ReadS CampaignResponse
ReadS [CampaignResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CampaignResponse]
$creadListPrec :: ReadPrec [CampaignResponse]
readPrec :: ReadPrec CampaignResponse
$creadPrec :: ReadPrec CampaignResponse
readList :: ReadS [CampaignResponse]
$creadList :: ReadS [CampaignResponse]
readsPrec :: Int -> ReadS CampaignResponse
$creadsPrec :: Int -> ReadS CampaignResponse
Prelude.Read, Int -> CampaignResponse -> ShowS
[CampaignResponse] -> ShowS
CampaignResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CampaignResponse] -> ShowS
$cshowList :: [CampaignResponse] -> ShowS
show :: CampaignResponse -> String
$cshow :: CampaignResponse -> String
showsPrec :: Int -> CampaignResponse -> ShowS
$cshowsPrec :: Int -> CampaignResponse -> ShowS
Prelude.Show, forall x. Rep CampaignResponse x -> CampaignResponse
forall x. CampaignResponse -> Rep CampaignResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CampaignResponse x -> CampaignResponse
$cfrom :: forall x. CampaignResponse -> Rep CampaignResponse x
Prelude.Generic)

-- |
-- Create a value of 'CampaignResponse' 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:
--
-- 'additionalTreatments', 'campaignResponse_additionalTreatments' - An array of responses, one for each treatment that you defined for the
-- campaign, in addition to the default treatment.
--
-- 'customDeliveryConfiguration', 'campaignResponse_customDeliveryConfiguration' - The delivery configuration settings for sending the campaign through a
-- custom channel.
--
-- 'defaultState', 'campaignResponse_defaultState' - The current status of the campaign\'s default treatment. This value
-- exists only for campaigns that have more than one treatment.
--
-- 'description', 'campaignResponse_description' - The custom description of the campaign.
--
-- 'holdoutPercent', 'campaignResponse_holdoutPercent' - The allocated percentage of users (segment members) who shouldn\'t
-- receive messages from the campaign.
--
-- 'hook', 'campaignResponse_hook' - The settings for the AWS Lambda function to use as a code hook for the
-- campaign. You can use this hook to customize the segment that\'s used by
-- the campaign.
--
-- 'isPaused', 'campaignResponse_isPaused' - Specifies whether the campaign is paused. A paused campaign doesn\'t run
-- unless you resume it by changing this value to false.
--
-- 'limits', 'campaignResponse_limits' - The messaging limits for the campaign.
--
-- 'messageConfiguration', 'campaignResponse_messageConfiguration' - The message configuration settings for the campaign.
--
-- 'name', 'campaignResponse_name' - The name of the campaign.
--
-- 'priority', 'campaignResponse_priority' - Defines the priority of the campaign, used to decide the order of
-- messages displayed to user if there are multiple messages scheduled to
-- be displayed at the same moment.
--
-- 'schedule', 'campaignResponse_schedule' - The schedule settings for the campaign.
--
-- 'state', 'campaignResponse_state' - The current status of the campaign.
--
-- 'templateConfiguration', 'campaignResponse_templateConfiguration' - The message template that’s used for the campaign.
--
-- 'treatmentDescription', 'campaignResponse_treatmentDescription' - The custom description of the default treatment for the campaign.
--
-- 'treatmentName', 'campaignResponse_treatmentName' - The custom name of the default treatment for the campaign, if the
-- campaign has multiple treatments. A /treatment/ is a variation of a
-- campaign that\'s used for A\/B testing.
--
-- 'version', 'campaignResponse_version' - The version number of the campaign.
--
-- 'tags', 'campaignResponse_tags' - A string-to-string map of key-value pairs that identifies the tags that
-- are associated with the campaign. Each tag consists of a required tag
-- key and an associated tag value.
--
-- 'lastModifiedDate', 'campaignResponse_lastModifiedDate' - The date, in ISO 8601 format, when the campaign was last modified.
--
-- 'creationDate', 'campaignResponse_creationDate' - The date, in ISO 8601 format, when the campaign was created.
--
-- 'segmentId', 'campaignResponse_segmentId' - The unique identifier for the segment that\'s associated with the
-- campaign.
--
-- 'segmentVersion', 'campaignResponse_segmentVersion' - The version number of the segment that\'s associated with the campaign.
--
-- 'id', 'campaignResponse_id' - The unique identifier for the campaign.
--
-- 'arn', 'campaignResponse_arn' - The Amazon Resource Name (ARN) of the campaign.
--
-- 'applicationId', 'campaignResponse_applicationId' - The unique identifier for the application that the campaign applies to.
newCampaignResponse ::
  -- | 'lastModifiedDate'
  Prelude.Text ->
  -- | 'creationDate'
  Prelude.Text ->
  -- | 'segmentId'
  Prelude.Text ->
  -- | 'segmentVersion'
  Prelude.Int ->
  -- | 'id'
  Prelude.Text ->
  -- | 'arn'
  Prelude.Text ->
  -- | 'applicationId'
  Prelude.Text ->
  CampaignResponse
newCampaignResponse :: Text
-> Text -> Text -> Int -> Text -> Text -> Text -> CampaignResponse
newCampaignResponse
  Text
pLastModifiedDate_
  Text
pCreationDate_
  Text
pSegmentId_
  Int
pSegmentVersion_
  Text
pId_
  Text
pArn_
  Text
pApplicationId_ =
    CampaignResponse'
      { $sel:additionalTreatments:CampaignResponse' :: Maybe [TreatmentResource]
additionalTreatments =
          forall a. Maybe a
Prelude.Nothing,
        $sel:customDeliveryConfiguration:CampaignResponse' :: Maybe CustomDeliveryConfiguration
customDeliveryConfiguration = forall a. Maybe a
Prelude.Nothing,
        $sel:defaultState:CampaignResponse' :: Maybe CampaignState
defaultState = forall a. Maybe a
Prelude.Nothing,
        $sel:description:CampaignResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:holdoutPercent:CampaignResponse' :: Maybe Int
holdoutPercent = forall a. Maybe a
Prelude.Nothing,
        $sel:hook:CampaignResponse' :: Maybe CampaignHook
hook = forall a. Maybe a
Prelude.Nothing,
        $sel:isPaused:CampaignResponse' :: Maybe Bool
isPaused = forall a. Maybe a
Prelude.Nothing,
        $sel:limits:CampaignResponse' :: Maybe CampaignLimits
limits = forall a. Maybe a
Prelude.Nothing,
        $sel:messageConfiguration:CampaignResponse' :: Maybe MessageConfiguration
messageConfiguration = forall a. Maybe a
Prelude.Nothing,
        $sel:name:CampaignResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
        $sel:priority:CampaignResponse' :: Maybe Int
priority = forall a. Maybe a
Prelude.Nothing,
        $sel:schedule:CampaignResponse' :: Maybe Schedule
schedule = forall a. Maybe a
Prelude.Nothing,
        $sel:state:CampaignResponse' :: Maybe CampaignState
state = forall a. Maybe a
Prelude.Nothing,
        $sel:templateConfiguration:CampaignResponse' :: Maybe TemplateConfiguration
templateConfiguration = forall a. Maybe a
Prelude.Nothing,
        $sel:treatmentDescription:CampaignResponse' :: Maybe Text
treatmentDescription = forall a. Maybe a
Prelude.Nothing,
        $sel:treatmentName:CampaignResponse' :: Maybe Text
treatmentName = forall a. Maybe a
Prelude.Nothing,
        $sel:version:CampaignResponse' :: Maybe Int
version = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CampaignResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:lastModifiedDate:CampaignResponse' :: Text
lastModifiedDate = Text
pLastModifiedDate_,
        $sel:creationDate:CampaignResponse' :: Text
creationDate = Text
pCreationDate_,
        $sel:segmentId:CampaignResponse' :: Text
segmentId = Text
pSegmentId_,
        $sel:segmentVersion:CampaignResponse' :: Int
segmentVersion = Int
pSegmentVersion_,
        $sel:id:CampaignResponse' :: Text
id = Text
pId_,
        $sel:arn:CampaignResponse' :: Text
arn = Text
pArn_,
        $sel:applicationId:CampaignResponse' :: Text
applicationId = Text
pApplicationId_
      }

-- | An array of responses, one for each treatment that you defined for the
-- campaign, in addition to the default treatment.
campaignResponse_additionalTreatments :: Lens.Lens' CampaignResponse (Prelude.Maybe [TreatmentResource])
campaignResponse_additionalTreatments :: Lens' CampaignResponse (Maybe [TreatmentResource])
campaignResponse_additionalTreatments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe [TreatmentResource]
additionalTreatments :: Maybe [TreatmentResource]
$sel:additionalTreatments:CampaignResponse' :: CampaignResponse -> Maybe [TreatmentResource]
additionalTreatments} -> Maybe [TreatmentResource]
additionalTreatments) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe [TreatmentResource]
a -> CampaignResponse
s {$sel:additionalTreatments:CampaignResponse' :: Maybe [TreatmentResource]
additionalTreatments = Maybe [TreatmentResource]
a} :: CampaignResponse) 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 delivery configuration settings for sending the campaign through a
-- custom channel.
campaignResponse_customDeliveryConfiguration :: Lens.Lens' CampaignResponse (Prelude.Maybe CustomDeliveryConfiguration)
campaignResponse_customDeliveryConfiguration :: Lens' CampaignResponse (Maybe CustomDeliveryConfiguration)
campaignResponse_customDeliveryConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe CustomDeliveryConfiguration
customDeliveryConfiguration :: Maybe CustomDeliveryConfiguration
$sel:customDeliveryConfiguration:CampaignResponse' :: CampaignResponse -> Maybe CustomDeliveryConfiguration
customDeliveryConfiguration} -> Maybe CustomDeliveryConfiguration
customDeliveryConfiguration) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe CustomDeliveryConfiguration
a -> CampaignResponse
s {$sel:customDeliveryConfiguration:CampaignResponse' :: Maybe CustomDeliveryConfiguration
customDeliveryConfiguration = Maybe CustomDeliveryConfiguration
a} :: CampaignResponse)

-- | The current status of the campaign\'s default treatment. This value
-- exists only for campaigns that have more than one treatment.
campaignResponse_defaultState :: Lens.Lens' CampaignResponse (Prelude.Maybe CampaignState)
campaignResponse_defaultState :: Lens' CampaignResponse (Maybe CampaignState)
campaignResponse_defaultState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe CampaignState
defaultState :: Maybe CampaignState
$sel:defaultState:CampaignResponse' :: CampaignResponse -> Maybe CampaignState
defaultState} -> Maybe CampaignState
defaultState) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe CampaignState
a -> CampaignResponse
s {$sel:defaultState:CampaignResponse' :: Maybe CampaignState
defaultState = Maybe CampaignState
a} :: CampaignResponse)

-- | The custom description of the campaign.
campaignResponse_description :: Lens.Lens' CampaignResponse (Prelude.Maybe Prelude.Text)
campaignResponse_description :: Lens' CampaignResponse (Maybe Text)
campaignResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe Text
description :: Maybe Text
$sel:description:CampaignResponse' :: CampaignResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe Text
a -> CampaignResponse
s {$sel:description:CampaignResponse' :: Maybe Text
description = Maybe Text
a} :: CampaignResponse)

-- | The allocated percentage of users (segment members) who shouldn\'t
-- receive messages from the campaign.
campaignResponse_holdoutPercent :: Lens.Lens' CampaignResponse (Prelude.Maybe Prelude.Int)
campaignResponse_holdoutPercent :: Lens' CampaignResponse (Maybe Int)
campaignResponse_holdoutPercent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe Int
holdoutPercent :: Maybe Int
$sel:holdoutPercent:CampaignResponse' :: CampaignResponse -> Maybe Int
holdoutPercent} -> Maybe Int
holdoutPercent) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe Int
a -> CampaignResponse
s {$sel:holdoutPercent:CampaignResponse' :: Maybe Int
holdoutPercent = Maybe Int
a} :: CampaignResponse)

-- | The settings for the AWS Lambda function to use as a code hook for the
-- campaign. You can use this hook to customize the segment that\'s used by
-- the campaign.
campaignResponse_hook :: Lens.Lens' CampaignResponse (Prelude.Maybe CampaignHook)
campaignResponse_hook :: Lens' CampaignResponse (Maybe CampaignHook)
campaignResponse_hook = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe CampaignHook
hook :: Maybe CampaignHook
$sel:hook:CampaignResponse' :: CampaignResponse -> Maybe CampaignHook
hook} -> Maybe CampaignHook
hook) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe CampaignHook
a -> CampaignResponse
s {$sel:hook:CampaignResponse' :: Maybe CampaignHook
hook = Maybe CampaignHook
a} :: CampaignResponse)

-- | Specifies whether the campaign is paused. A paused campaign doesn\'t run
-- unless you resume it by changing this value to false.
campaignResponse_isPaused :: Lens.Lens' CampaignResponse (Prelude.Maybe Prelude.Bool)
campaignResponse_isPaused :: Lens' CampaignResponse (Maybe Bool)
campaignResponse_isPaused = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe Bool
isPaused :: Maybe Bool
$sel:isPaused:CampaignResponse' :: CampaignResponse -> Maybe Bool
isPaused} -> Maybe Bool
isPaused) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe Bool
a -> CampaignResponse
s {$sel:isPaused:CampaignResponse' :: Maybe Bool
isPaused = Maybe Bool
a} :: CampaignResponse)

-- | The messaging limits for the campaign.
campaignResponse_limits :: Lens.Lens' CampaignResponse (Prelude.Maybe CampaignLimits)
campaignResponse_limits :: Lens' CampaignResponse (Maybe CampaignLimits)
campaignResponse_limits = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe CampaignLimits
limits :: Maybe CampaignLimits
$sel:limits:CampaignResponse' :: CampaignResponse -> Maybe CampaignLimits
limits} -> Maybe CampaignLimits
limits) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe CampaignLimits
a -> CampaignResponse
s {$sel:limits:CampaignResponse' :: Maybe CampaignLimits
limits = Maybe CampaignLimits
a} :: CampaignResponse)

-- | The message configuration settings for the campaign.
campaignResponse_messageConfiguration :: Lens.Lens' CampaignResponse (Prelude.Maybe MessageConfiguration)
campaignResponse_messageConfiguration :: Lens' CampaignResponse (Maybe MessageConfiguration)
campaignResponse_messageConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe MessageConfiguration
messageConfiguration :: Maybe MessageConfiguration
$sel:messageConfiguration:CampaignResponse' :: CampaignResponse -> Maybe MessageConfiguration
messageConfiguration} -> Maybe MessageConfiguration
messageConfiguration) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe MessageConfiguration
a -> CampaignResponse
s {$sel:messageConfiguration:CampaignResponse' :: Maybe MessageConfiguration
messageConfiguration = Maybe MessageConfiguration
a} :: CampaignResponse)

-- | The name of the campaign.
campaignResponse_name :: Lens.Lens' CampaignResponse (Prelude.Maybe Prelude.Text)
campaignResponse_name :: Lens' CampaignResponse (Maybe Text)
campaignResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe Text
name :: Maybe Text
$sel:name:CampaignResponse' :: CampaignResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe Text
a -> CampaignResponse
s {$sel:name:CampaignResponse' :: Maybe Text
name = Maybe Text
a} :: CampaignResponse)

-- | Defines the priority of the campaign, used to decide the order of
-- messages displayed to user if there are multiple messages scheduled to
-- be displayed at the same moment.
campaignResponse_priority :: Lens.Lens' CampaignResponse (Prelude.Maybe Prelude.Int)
campaignResponse_priority :: Lens' CampaignResponse (Maybe Int)
campaignResponse_priority = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe Int
priority :: Maybe Int
$sel:priority:CampaignResponse' :: CampaignResponse -> Maybe Int
priority} -> Maybe Int
priority) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe Int
a -> CampaignResponse
s {$sel:priority:CampaignResponse' :: Maybe Int
priority = Maybe Int
a} :: CampaignResponse)

-- | The schedule settings for the campaign.
campaignResponse_schedule :: Lens.Lens' CampaignResponse (Prelude.Maybe Schedule)
campaignResponse_schedule :: Lens' CampaignResponse (Maybe Schedule)
campaignResponse_schedule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe Schedule
schedule :: Maybe Schedule
$sel:schedule:CampaignResponse' :: CampaignResponse -> Maybe Schedule
schedule} -> Maybe Schedule
schedule) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe Schedule
a -> CampaignResponse
s {$sel:schedule:CampaignResponse' :: Maybe Schedule
schedule = Maybe Schedule
a} :: CampaignResponse)

-- | The current status of the campaign.
campaignResponse_state :: Lens.Lens' CampaignResponse (Prelude.Maybe CampaignState)
campaignResponse_state :: Lens' CampaignResponse (Maybe CampaignState)
campaignResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe CampaignState
state :: Maybe CampaignState
$sel:state:CampaignResponse' :: CampaignResponse -> Maybe CampaignState
state} -> Maybe CampaignState
state) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe CampaignState
a -> CampaignResponse
s {$sel:state:CampaignResponse' :: Maybe CampaignState
state = Maybe CampaignState
a} :: CampaignResponse)

-- | The message template that’s used for the campaign.
campaignResponse_templateConfiguration :: Lens.Lens' CampaignResponse (Prelude.Maybe TemplateConfiguration)
campaignResponse_templateConfiguration :: Lens' CampaignResponse (Maybe TemplateConfiguration)
campaignResponse_templateConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe TemplateConfiguration
templateConfiguration :: Maybe TemplateConfiguration
$sel:templateConfiguration:CampaignResponse' :: CampaignResponse -> Maybe TemplateConfiguration
templateConfiguration} -> Maybe TemplateConfiguration
templateConfiguration) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe TemplateConfiguration
a -> CampaignResponse
s {$sel:templateConfiguration:CampaignResponse' :: Maybe TemplateConfiguration
templateConfiguration = Maybe TemplateConfiguration
a} :: CampaignResponse)

-- | The custom description of the default treatment for the campaign.
campaignResponse_treatmentDescription :: Lens.Lens' CampaignResponse (Prelude.Maybe Prelude.Text)
campaignResponse_treatmentDescription :: Lens' CampaignResponse (Maybe Text)
campaignResponse_treatmentDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe Text
treatmentDescription :: Maybe Text
$sel:treatmentDescription:CampaignResponse' :: CampaignResponse -> Maybe Text
treatmentDescription} -> Maybe Text
treatmentDescription) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe Text
a -> CampaignResponse
s {$sel:treatmentDescription:CampaignResponse' :: Maybe Text
treatmentDescription = Maybe Text
a} :: CampaignResponse)

-- | The custom name of the default treatment for the campaign, if the
-- campaign has multiple treatments. A /treatment/ is a variation of a
-- campaign that\'s used for A\/B testing.
campaignResponse_treatmentName :: Lens.Lens' CampaignResponse (Prelude.Maybe Prelude.Text)
campaignResponse_treatmentName :: Lens' CampaignResponse (Maybe Text)
campaignResponse_treatmentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe Text
treatmentName :: Maybe Text
$sel:treatmentName:CampaignResponse' :: CampaignResponse -> Maybe Text
treatmentName} -> Maybe Text
treatmentName) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe Text
a -> CampaignResponse
s {$sel:treatmentName:CampaignResponse' :: Maybe Text
treatmentName = Maybe Text
a} :: CampaignResponse)

-- | The version number of the campaign.
campaignResponse_version :: Lens.Lens' CampaignResponse (Prelude.Maybe Prelude.Int)
campaignResponse_version :: Lens' CampaignResponse (Maybe Int)
campaignResponse_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe Int
version :: Maybe Int
$sel:version:CampaignResponse' :: CampaignResponse -> Maybe Int
version} -> Maybe Int
version) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe Int
a -> CampaignResponse
s {$sel:version:CampaignResponse' :: Maybe Int
version = Maybe Int
a} :: CampaignResponse)

-- | A string-to-string map of key-value pairs that identifies the tags that
-- are associated with the campaign. Each tag consists of a required tag
-- key and an associated tag value.
campaignResponse_tags :: Lens.Lens' CampaignResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
campaignResponse_tags :: Lens' CampaignResponse (Maybe (HashMap Text Text))
campaignResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CampaignResponse' :: CampaignResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CampaignResponse
s@CampaignResponse' {} Maybe (HashMap Text Text)
a -> CampaignResponse
s {$sel:tags:CampaignResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CampaignResponse) 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 date, in ISO 8601 format, when the campaign was last modified.
campaignResponse_lastModifiedDate :: Lens.Lens' CampaignResponse Prelude.Text
campaignResponse_lastModifiedDate :: Lens' CampaignResponse Text
campaignResponse_lastModifiedDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Text
lastModifiedDate :: Text
$sel:lastModifiedDate:CampaignResponse' :: CampaignResponse -> Text
lastModifiedDate} -> Text
lastModifiedDate) (\s :: CampaignResponse
s@CampaignResponse' {} Text
a -> CampaignResponse
s {$sel:lastModifiedDate:CampaignResponse' :: Text
lastModifiedDate = Text
a} :: CampaignResponse)

-- | The date, in ISO 8601 format, when the campaign was created.
campaignResponse_creationDate :: Lens.Lens' CampaignResponse Prelude.Text
campaignResponse_creationDate :: Lens' CampaignResponse Text
campaignResponse_creationDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Text
creationDate :: Text
$sel:creationDate:CampaignResponse' :: CampaignResponse -> Text
creationDate} -> Text
creationDate) (\s :: CampaignResponse
s@CampaignResponse' {} Text
a -> CampaignResponse
s {$sel:creationDate:CampaignResponse' :: Text
creationDate = Text
a} :: CampaignResponse)

-- | The unique identifier for the segment that\'s associated with the
-- campaign.
campaignResponse_segmentId :: Lens.Lens' CampaignResponse Prelude.Text
campaignResponse_segmentId :: Lens' CampaignResponse Text
campaignResponse_segmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Text
segmentId :: Text
$sel:segmentId:CampaignResponse' :: CampaignResponse -> Text
segmentId} -> Text
segmentId) (\s :: CampaignResponse
s@CampaignResponse' {} Text
a -> CampaignResponse
s {$sel:segmentId:CampaignResponse' :: Text
segmentId = Text
a} :: CampaignResponse)

-- | The version number of the segment that\'s associated with the campaign.
campaignResponse_segmentVersion :: Lens.Lens' CampaignResponse Prelude.Int
campaignResponse_segmentVersion :: Lens' CampaignResponse Int
campaignResponse_segmentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Int
segmentVersion :: Int
$sel:segmentVersion:CampaignResponse' :: CampaignResponse -> Int
segmentVersion} -> Int
segmentVersion) (\s :: CampaignResponse
s@CampaignResponse' {} Int
a -> CampaignResponse
s {$sel:segmentVersion:CampaignResponse' :: Int
segmentVersion = Int
a} :: CampaignResponse)

-- | The unique identifier for the campaign.
campaignResponse_id :: Lens.Lens' CampaignResponse Prelude.Text
campaignResponse_id :: Lens' CampaignResponse Text
campaignResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Text
id :: Text
$sel:id:CampaignResponse' :: CampaignResponse -> Text
id} -> Text
id) (\s :: CampaignResponse
s@CampaignResponse' {} Text
a -> CampaignResponse
s {$sel:id:CampaignResponse' :: Text
id = Text
a} :: CampaignResponse)

-- | The Amazon Resource Name (ARN) of the campaign.
campaignResponse_arn :: Lens.Lens' CampaignResponse Prelude.Text
campaignResponse_arn :: Lens' CampaignResponse Text
campaignResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Text
arn :: Text
$sel:arn:CampaignResponse' :: CampaignResponse -> Text
arn} -> Text
arn) (\s :: CampaignResponse
s@CampaignResponse' {} Text
a -> CampaignResponse
s {$sel:arn:CampaignResponse' :: Text
arn = Text
a} :: CampaignResponse)

-- | The unique identifier for the application that the campaign applies to.
campaignResponse_applicationId :: Lens.Lens' CampaignResponse Prelude.Text
campaignResponse_applicationId :: Lens' CampaignResponse Text
campaignResponse_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CampaignResponse' {Text
applicationId :: Text
$sel:applicationId:CampaignResponse' :: CampaignResponse -> Text
applicationId} -> Text
applicationId) (\s :: CampaignResponse
s@CampaignResponse' {} Text
a -> CampaignResponse
s {$sel:applicationId:CampaignResponse' :: Text
applicationId = Text
a} :: CampaignResponse)

instance Data.FromJSON CampaignResponse where
  parseJSON :: Value -> Parser CampaignResponse
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"CampaignResponse"
      ( \Object
x ->
          Maybe [TreatmentResource]
-> Maybe CustomDeliveryConfiguration
-> Maybe CampaignState
-> Maybe Text
-> Maybe Int
-> Maybe CampaignHook
-> Maybe Bool
-> Maybe CampaignLimits
-> Maybe MessageConfiguration
-> Maybe Text
-> Maybe Int
-> Maybe Schedule
-> Maybe CampaignState
-> Maybe TemplateConfiguration
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe (HashMap Text Text)
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> CampaignResponse
CampaignResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AdditionalTreatments"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CustomDeliveryConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DefaultState")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"HoldoutPercent")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Hook")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"IsPaused")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Limits")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MessageConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Priority")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Schedule")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"State")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"TemplateConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"TreatmentDescription")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"TreatmentName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Version")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"LastModifiedDate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"CreationDate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"SegmentId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"SegmentVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"ApplicationId")
      )

instance Prelude.Hashable CampaignResponse where
  hashWithSalt :: Int -> CampaignResponse -> Int
hashWithSalt Int
_salt CampaignResponse' {Int
Maybe Bool
Maybe Int
Maybe [TreatmentResource]
Maybe Text
Maybe (HashMap Text Text)
Maybe CampaignLimits
Maybe CampaignState
Maybe CustomDeliveryConfiguration
Maybe CampaignHook
Maybe MessageConfiguration
Maybe Schedule
Maybe TemplateConfiguration
Text
applicationId :: Text
arn :: Text
id :: Text
segmentVersion :: Int
segmentId :: Text
creationDate :: Text
lastModifiedDate :: Text
tags :: Maybe (HashMap Text Text)
version :: Maybe Int
treatmentName :: Maybe Text
treatmentDescription :: Maybe Text
templateConfiguration :: Maybe TemplateConfiguration
state :: Maybe CampaignState
schedule :: Maybe Schedule
priority :: Maybe Int
name :: Maybe Text
messageConfiguration :: Maybe MessageConfiguration
limits :: Maybe CampaignLimits
isPaused :: Maybe Bool
hook :: Maybe CampaignHook
holdoutPercent :: Maybe Int
description :: Maybe Text
defaultState :: Maybe CampaignState
customDeliveryConfiguration :: Maybe CustomDeliveryConfiguration
additionalTreatments :: Maybe [TreatmentResource]
$sel:applicationId:CampaignResponse' :: CampaignResponse -> Text
$sel:arn:CampaignResponse' :: CampaignResponse -> Text
$sel:id:CampaignResponse' :: CampaignResponse -> Text
$sel:segmentVersion:CampaignResponse' :: CampaignResponse -> Int
$sel:segmentId:CampaignResponse' :: CampaignResponse -> Text
$sel:creationDate:CampaignResponse' :: CampaignResponse -> Text
$sel:lastModifiedDate:CampaignResponse' :: CampaignResponse -> Text
$sel:tags:CampaignResponse' :: CampaignResponse -> Maybe (HashMap Text Text)
$sel:version:CampaignResponse' :: CampaignResponse -> Maybe Int
$sel:treatmentName:CampaignResponse' :: CampaignResponse -> Maybe Text
$sel:treatmentDescription:CampaignResponse' :: CampaignResponse -> Maybe Text
$sel:templateConfiguration:CampaignResponse' :: CampaignResponse -> Maybe TemplateConfiguration
$sel:state:CampaignResponse' :: CampaignResponse -> Maybe CampaignState
$sel:schedule:CampaignResponse' :: CampaignResponse -> Maybe Schedule
$sel:priority:CampaignResponse' :: CampaignResponse -> Maybe Int
$sel:name:CampaignResponse' :: CampaignResponse -> Maybe Text
$sel:messageConfiguration:CampaignResponse' :: CampaignResponse -> Maybe MessageConfiguration
$sel:limits:CampaignResponse' :: CampaignResponse -> Maybe CampaignLimits
$sel:isPaused:CampaignResponse' :: CampaignResponse -> Maybe Bool
$sel:hook:CampaignResponse' :: CampaignResponse -> Maybe CampaignHook
$sel:holdoutPercent:CampaignResponse' :: CampaignResponse -> Maybe Int
$sel:description:CampaignResponse' :: CampaignResponse -> Maybe Text
$sel:defaultState:CampaignResponse' :: CampaignResponse -> Maybe CampaignState
$sel:customDeliveryConfiguration:CampaignResponse' :: CampaignResponse -> Maybe CustomDeliveryConfiguration
$sel:additionalTreatments:CampaignResponse' :: CampaignResponse -> Maybe [TreatmentResource]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [TreatmentResource]
additionalTreatments
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CustomDeliveryConfiguration
customDeliveryConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CampaignState
defaultState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
holdoutPercent
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CampaignHook
hook
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
isPaused
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CampaignLimits
limits
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MessageConfiguration
messageConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
priority
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Schedule
schedule
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CampaignState
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TemplateConfiguration
templateConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
treatmentDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
treatmentName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
version
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
lastModifiedDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
creationDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
segmentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
segmentVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId

instance Prelude.NFData CampaignResponse where
  rnf :: CampaignResponse -> ()
rnf CampaignResponse' {Int
Maybe Bool
Maybe Int
Maybe [TreatmentResource]
Maybe Text
Maybe (HashMap Text Text)
Maybe CampaignLimits
Maybe CampaignState
Maybe CustomDeliveryConfiguration
Maybe CampaignHook
Maybe MessageConfiguration
Maybe Schedule
Maybe TemplateConfiguration
Text
applicationId :: Text
arn :: Text
id :: Text
segmentVersion :: Int
segmentId :: Text
creationDate :: Text
lastModifiedDate :: Text
tags :: Maybe (HashMap Text Text)
version :: Maybe Int
treatmentName :: Maybe Text
treatmentDescription :: Maybe Text
templateConfiguration :: Maybe TemplateConfiguration
state :: Maybe CampaignState
schedule :: Maybe Schedule
priority :: Maybe Int
name :: Maybe Text
messageConfiguration :: Maybe MessageConfiguration
limits :: Maybe CampaignLimits
isPaused :: Maybe Bool
hook :: Maybe CampaignHook
holdoutPercent :: Maybe Int
description :: Maybe Text
defaultState :: Maybe CampaignState
customDeliveryConfiguration :: Maybe CustomDeliveryConfiguration
additionalTreatments :: Maybe [TreatmentResource]
$sel:applicationId:CampaignResponse' :: CampaignResponse -> Text
$sel:arn:CampaignResponse' :: CampaignResponse -> Text
$sel:id:CampaignResponse' :: CampaignResponse -> Text
$sel:segmentVersion:CampaignResponse' :: CampaignResponse -> Int
$sel:segmentId:CampaignResponse' :: CampaignResponse -> Text
$sel:creationDate:CampaignResponse' :: CampaignResponse -> Text
$sel:lastModifiedDate:CampaignResponse' :: CampaignResponse -> Text
$sel:tags:CampaignResponse' :: CampaignResponse -> Maybe (HashMap Text Text)
$sel:version:CampaignResponse' :: CampaignResponse -> Maybe Int
$sel:treatmentName:CampaignResponse' :: CampaignResponse -> Maybe Text
$sel:treatmentDescription:CampaignResponse' :: CampaignResponse -> Maybe Text
$sel:templateConfiguration:CampaignResponse' :: CampaignResponse -> Maybe TemplateConfiguration
$sel:state:CampaignResponse' :: CampaignResponse -> Maybe CampaignState
$sel:schedule:CampaignResponse' :: CampaignResponse -> Maybe Schedule
$sel:priority:CampaignResponse' :: CampaignResponse -> Maybe Int
$sel:name:CampaignResponse' :: CampaignResponse -> Maybe Text
$sel:messageConfiguration:CampaignResponse' :: CampaignResponse -> Maybe MessageConfiguration
$sel:limits:CampaignResponse' :: CampaignResponse -> Maybe CampaignLimits
$sel:isPaused:CampaignResponse' :: CampaignResponse -> Maybe Bool
$sel:hook:CampaignResponse' :: CampaignResponse -> Maybe CampaignHook
$sel:holdoutPercent:CampaignResponse' :: CampaignResponse -> Maybe Int
$sel:description:CampaignResponse' :: CampaignResponse -> Maybe Text
$sel:defaultState:CampaignResponse' :: CampaignResponse -> Maybe CampaignState
$sel:customDeliveryConfiguration:CampaignResponse' :: CampaignResponse -> Maybe CustomDeliveryConfiguration
$sel:additionalTreatments:CampaignResponse' :: CampaignResponse -> Maybe [TreatmentResource]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [TreatmentResource]
additionalTreatments
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CustomDeliveryConfiguration
customDeliveryConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CampaignState
defaultState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
holdoutPercent
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CampaignHook
hook
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
isPaused
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CampaignLimits
limits
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MessageConfiguration
messageConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
priority
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Schedule
schedule
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CampaignState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TemplateConfiguration
templateConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
treatmentDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
treatmentName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
lastModifiedDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
creationDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
segmentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
segmentVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
applicationId