amazonka-pinpoint-1.5.0: Amazon Pinpoint SDK.

Copyright(c) 2013-2017 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay+amazonka@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.AWS.Pinpoint

Contents

Description

Amazon Pinpoint makes it easy to run targeted campaigns to drive user engagement in mobile apps. Amazon Pinpoint helps you understand user behavior, define which users to target, determine which messages to send, schedule the best time to deliver the messages, and then track the results of your campaign.

Targeted push notifications based on app usage trends and user behavior have become a popular approach for mobile app user engagement because response rates are often several times higher than tradition email marketing campaigns. By using targeted push notifications, you can increase message relevance and effectiveness, measure engagement, and continually improve your campaigns.

Getting started with Amazon Pinpoint is easy. First, AWS Mobile Hub guides you through the process to integrate the AWS Mobile SDK with your app. Next, you define your target segments, campaign message, and specify the delivery schedule. Once your campaign is running, Pinpoint provides metrics so you can run analytics and track the impact of your campaign.

With Amazon Pinpoint, there are no upfront setup costs, and no fixed monthly cost. You only pay for the number of users your campaign targets, the messages you send, and the events you collect, so you can start small and scale as your application grows.

Synopsis

Service Configuration

pinpoint :: Service Source #

API version 2016-12-01 of the Amazon Pinpoint SDK configuration.

Errors

Error matchers are designed for use with the functions provided by Control.Exception.Lens. This allows catching (and rethrowing) service specific errors returned by Pinpoint.

ForbiddenException

NotFoundException

TooManyRequestsException

InternalServerErrorException

MethodNotAllowedException

BadRequestException

Waiters

Waiters poll by repeatedly sending a request until some remote success condition configured by the Wait specification is fulfilled. The Wait specification determines how many attempts should be made, in addition to delay and retry strategies.

Operations

Some AWS operations return results that are incomplete and require subsequent requests in order to obtain the entire result set. The process of sending subsequent requests to continue where a previous request left off is called pagination. For example, the ListObjects operation of Amazon S3 returns up to 1000 objects at a time, and you must send subsequent requests with the appropriate Marker in order to retrieve the next page of results.

Operations that have an AWSPager instance can transparently perform subsequent requests, correctly setting Markers and other request facets to iterate through the entire result set of a truncated API operation. Operations which support this have an additional note in the documentation.

Many operations have the ability to filter results on the server side. See the individual operation parameters for details.

GetGCMChannel

GetSegmentImportJobs

SendMessages

GetImportJob

GetAPNSVoipSandboxChannel

GetSegmentVersions

DeleteCampaign

UpdateCampaign

GetSegmentVersion

CreateSegment

UpdateADMChannel

DeleteADMChannel

UpdateEndpoint

CreateCampaign

GetEndpoint

GetSegment

UpdateEndpointsBatch

GetADMChannel

GetCampaign

DeleteApp

UpdateAPNSVoipSandboxChannel

DeleteAPNSVoipSandboxChannel

UpdateGCMChannel

DeleteGCMChannel

GetCampaignActivities

GetEventStream

DeleteEmailChannel

UpdateEmailChannel

GetBaiduChannel

DeleteAPNSChannel

UpdateAPNSChannel

PutEventStream

DeleteEventStream

GetCampaignVersions

GetAPNSChannel

GetApps

GetAPNSSandboxChannel

GetImportJobs

DeleteSmsChannel

UpdateSmsChannel

GetApp

GetCampaignVersion

DeleteSegment

UpdateSegment

CreateApp

GetSmsChannel

DeleteAPNSSandboxChannel

UpdateAPNSSandboxChannel

GetCampaigns

UpdateApplicationSettings

GetSegments

CreateImportJob

DeleteAPNSVoipChannel

UpdateAPNSVoipChannel

SendUsersMessages

GetApplicationSettings

DeleteBaiduChannel

UpdateBaiduChannel

GetAPNSVoipChannel

GetEmailChannel

Types

Action

data Action Source #

Constructors

DeepLink 
OpenApp 
URL 

Instances

Bounded Action Source # 
Enum Action Source # 
Eq Action Source # 

Methods

(==) :: Action -> Action -> Bool #

(/=) :: Action -> Action -> Bool #

Data Action Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Action -> c Action #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Action #

toConstr :: Action -> Constr #

dataTypeOf :: Action -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Action) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Action) #

gmapT :: (forall b. Data b => b -> b) -> Action -> Action #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Action -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Action -> r #

gmapQ :: (forall d. Data d => d -> u) -> Action -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Action -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Action -> m Action #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Action -> m Action #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Action -> m Action #

Ord Action Source # 
Read Action Source # 
Show Action Source # 
Generic Action Source # 

Associated Types

type Rep Action :: * -> * #

Methods

from :: Action -> Rep Action x #

to :: Rep Action x -> Action #

Hashable Action Source # 

Methods

hashWithSalt :: Int -> Action -> Int #

hash :: Action -> Int #

FromJSON Action Source # 
ToJSON Action Source # 
NFData Action Source # 

Methods

rnf :: Action -> () #

ToQuery Action Source # 
ToHeader Action Source # 

Methods

toHeader :: HeaderName -> Action -> [Header] #

ToByteString Action Source # 

Methods

toBS :: Action -> ByteString #

FromText Action Source # 

Methods

parser :: Parser Action #

ToText Action Source # 

Methods

toText :: Action -> Text #

type Rep Action Source # 
type Rep Action = D1 (MetaData "Action" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) (C1 (MetaCons "DeepLink" PrefixI False) U1) ((:+:) (C1 (MetaCons "OpenApp" PrefixI False) U1) (C1 (MetaCons "URL" PrefixI False) U1)))

AttributeType

data AttributeType Source #

Constructors

Exclusive 
Inclusive 

Instances

Bounded AttributeType Source # 
Enum AttributeType Source # 
Eq AttributeType Source # 
Data AttributeType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AttributeType -> c AttributeType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AttributeType #

toConstr :: AttributeType -> Constr #

dataTypeOf :: AttributeType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AttributeType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AttributeType) #

gmapT :: (forall b. Data b => b -> b) -> AttributeType -> AttributeType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AttributeType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AttributeType -> r #

gmapQ :: (forall d. Data d => d -> u) -> AttributeType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AttributeType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AttributeType -> m AttributeType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeType -> m AttributeType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeType -> m AttributeType #

Ord AttributeType Source # 
Read AttributeType Source # 
Show AttributeType Source # 
Generic AttributeType Source # 

Associated Types

type Rep AttributeType :: * -> * #

Hashable AttributeType Source # 
FromJSON AttributeType Source # 
ToJSON AttributeType Source # 
NFData AttributeType Source # 

Methods

rnf :: AttributeType -> () #

ToQuery AttributeType Source # 
ToHeader AttributeType Source # 
ToByteString AttributeType Source # 
FromText AttributeType Source # 
ToText AttributeType Source # 

Methods

toText :: AttributeType -> Text #

type Rep AttributeType Source # 
type Rep AttributeType = D1 (MetaData "AttributeType" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) (C1 (MetaCons "Exclusive" PrefixI False) U1) (C1 (MetaCons "Inclusive" PrefixI False) U1))

CampaignStatus

data CampaignStatus Source #

Instances

Bounded CampaignStatus Source # 
Enum CampaignStatus Source # 
Eq CampaignStatus Source # 
Data CampaignStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CampaignStatus -> c CampaignStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CampaignStatus #

toConstr :: CampaignStatus -> Constr #

dataTypeOf :: CampaignStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CampaignStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CampaignStatus) #

gmapT :: (forall b. Data b => b -> b) -> CampaignStatus -> CampaignStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CampaignStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CampaignStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> CampaignStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CampaignStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CampaignStatus -> m CampaignStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignStatus -> m CampaignStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignStatus -> m CampaignStatus #

Ord CampaignStatus Source # 
Read CampaignStatus Source # 
Show CampaignStatus Source # 
Generic CampaignStatus Source # 

Associated Types

type Rep CampaignStatus :: * -> * #

Hashable CampaignStatus Source # 
FromJSON CampaignStatus Source # 
NFData CampaignStatus Source # 

Methods

rnf :: CampaignStatus -> () #

ToQuery CampaignStatus Source # 
ToHeader CampaignStatus Source # 
ToByteString CampaignStatus Source # 
FromText CampaignStatus Source # 
ToText CampaignStatus Source # 
type Rep CampaignStatus Source # 
type Rep CampaignStatus = D1 (MetaData "CampaignStatus" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) ((:+:) (C1 (MetaCons "Completed" PrefixI False) U1) (C1 (MetaCons "Executing" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Paused" PrefixI False) U1) ((:+:) (C1 (MetaCons "PendingNextRun" PrefixI False) U1) (C1 (MetaCons "Scheduled" PrefixI False) U1))))

ChannelType

data ChannelType Source #

Instances

Bounded ChannelType Source # 
Enum ChannelType Source # 
Eq ChannelType Source # 
Data ChannelType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChannelType -> c ChannelType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChannelType #

toConstr :: ChannelType -> Constr #

dataTypeOf :: ChannelType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChannelType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChannelType) #

gmapT :: (forall b. Data b => b -> b) -> ChannelType -> ChannelType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChannelType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChannelType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChannelType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChannelType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChannelType -> m ChannelType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChannelType -> m ChannelType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChannelType -> m ChannelType #

Ord ChannelType Source # 
Read ChannelType Source # 
Show ChannelType Source # 
Generic ChannelType Source # 

Associated Types

type Rep ChannelType :: * -> * #

Hashable ChannelType Source # 
FromJSON ChannelType Source # 
ToJSON ChannelType Source # 
NFData ChannelType Source # 

Methods

rnf :: ChannelType -> () #

ToQuery ChannelType Source # 
ToHeader ChannelType Source # 
ToByteString ChannelType Source # 
FromText ChannelType Source # 
ToText ChannelType Source # 

Methods

toText :: ChannelType -> Text #

type Rep ChannelType Source # 
type Rep ChannelType = D1 (MetaData "ChannelType" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ADM" PrefixI False) U1) (C1 (MetaCons "APNS" PrefixI False) U1)) ((:+:) (C1 (MetaCons "APNSSandbox" PrefixI False) U1) (C1 (MetaCons "APNSVoip" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "APNSVoipSandbox" PrefixI False) U1) (C1 (MetaCons "Baidu" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Email" PrefixI False) U1) ((:+:) (C1 (MetaCons "GCM" PrefixI False) U1) (C1 (MetaCons "Sms" PrefixI False) U1)))))

DefinitionFormat

data DefinitionFormat Source #

Constructors

CSV 
JSON 

Instances

Bounded DefinitionFormat Source # 
Enum DefinitionFormat Source # 
Eq DefinitionFormat Source # 
Data DefinitionFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefinitionFormat -> c DefinitionFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DefinitionFormat #

toConstr :: DefinitionFormat -> Constr #

dataTypeOf :: DefinitionFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DefinitionFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DefinitionFormat) #

gmapT :: (forall b. Data b => b -> b) -> DefinitionFormat -> DefinitionFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefinitionFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefinitionFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> DefinitionFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DefinitionFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefinitionFormat -> m DefinitionFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefinitionFormat -> m DefinitionFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefinitionFormat -> m DefinitionFormat #

Ord DefinitionFormat Source # 
Read DefinitionFormat Source # 
Show DefinitionFormat Source # 
Generic DefinitionFormat Source # 
Hashable DefinitionFormat Source # 
FromJSON DefinitionFormat Source # 
ToJSON DefinitionFormat Source # 
NFData DefinitionFormat Source # 

Methods

rnf :: DefinitionFormat -> () #

ToQuery DefinitionFormat Source # 
ToHeader DefinitionFormat Source # 
ToByteString DefinitionFormat Source # 
FromText DefinitionFormat Source # 
ToText DefinitionFormat Source # 
type Rep DefinitionFormat Source # 
type Rep DefinitionFormat = D1 (MetaData "DefinitionFormat" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) (C1 (MetaCons "CSV" PrefixI False) U1) (C1 (MetaCons "JSON" PrefixI False) U1))

DeliveryStatus

data DeliveryStatus Source #

Instances

Bounded DeliveryStatus Source # 
Enum DeliveryStatus Source # 
Eq DeliveryStatus Source # 
Data DeliveryStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeliveryStatus -> c DeliveryStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeliveryStatus #

toConstr :: DeliveryStatus -> Constr #

dataTypeOf :: DeliveryStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeliveryStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeliveryStatus) #

gmapT :: (forall b. Data b => b -> b) -> DeliveryStatus -> DeliveryStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeliveryStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeliveryStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeliveryStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeliveryStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeliveryStatus -> m DeliveryStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeliveryStatus -> m DeliveryStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeliveryStatus -> m DeliveryStatus #

Ord DeliveryStatus Source # 
Read DeliveryStatus Source # 
Show DeliveryStatus Source # 
Generic DeliveryStatus Source # 

Associated Types

type Rep DeliveryStatus :: * -> * #

Hashable DeliveryStatus Source # 
FromJSON DeliveryStatus Source # 
NFData DeliveryStatus Source # 

Methods

rnf :: DeliveryStatus -> () #

ToQuery DeliveryStatus Source # 
ToHeader DeliveryStatus Source # 
ToByteString DeliveryStatus Source # 
FromText DeliveryStatus Source # 
ToText DeliveryStatus Source # 
type Rep DeliveryStatus Source # 
type Rep DeliveryStatus = D1 (MetaData "DeliveryStatus" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) ((:+:) (C1 (MetaCons "Duplicate" PrefixI False) U1) ((:+:) (C1 (MetaCons "OptOut" PrefixI False) U1) (C1 (MetaCons "PermanentFailure" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Successful" PrefixI False) U1) (C1 (MetaCons "TemporaryFailure" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Throttled" PrefixI False) U1) (C1 (MetaCons "UnknownFailure" PrefixI False) U1))))

DimensionType

data DimensionType Source #

Constructors

DTExclusive 
DTInclusive 

Instances

Bounded DimensionType Source # 
Enum DimensionType Source # 
Eq DimensionType Source # 
Data DimensionType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DimensionType -> c DimensionType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DimensionType #

toConstr :: DimensionType -> Constr #

dataTypeOf :: DimensionType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DimensionType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DimensionType) #

gmapT :: (forall b. Data b => b -> b) -> DimensionType -> DimensionType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DimensionType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DimensionType -> r #

gmapQ :: (forall d. Data d => d -> u) -> DimensionType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DimensionType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DimensionType -> m DimensionType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionType -> m DimensionType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionType -> m DimensionType #

Ord DimensionType Source # 
Read DimensionType Source # 
Show DimensionType Source # 
Generic DimensionType Source # 

Associated Types

type Rep DimensionType :: * -> * #

Hashable DimensionType Source # 
FromJSON DimensionType Source # 
ToJSON DimensionType Source # 
NFData DimensionType Source # 

Methods

rnf :: DimensionType -> () #

ToQuery DimensionType Source # 
ToHeader DimensionType Source # 
ToByteString DimensionType Source # 
FromText DimensionType Source # 
ToText DimensionType Source # 

Methods

toText :: DimensionType -> Text #

type Rep DimensionType Source # 
type Rep DimensionType = D1 (MetaData "DimensionType" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) (C1 (MetaCons "DTExclusive" PrefixI False) U1) (C1 (MetaCons "DTInclusive" PrefixI False) U1))

Duration

data Duration Source #

Constructors

Day14 
Day30 
Day7 
Hr24 

Instances

Bounded Duration Source # 
Enum Duration Source # 
Eq Duration Source # 
Data Duration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Duration -> c Duration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Duration #

toConstr :: Duration -> Constr #

dataTypeOf :: Duration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Duration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Duration) #

gmapT :: (forall b. Data b => b -> b) -> Duration -> Duration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Duration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Duration -> r #

gmapQ :: (forall d. Data d => d -> u) -> Duration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Duration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Duration -> m Duration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Duration -> m Duration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Duration -> m Duration #

Ord Duration Source # 
Read Duration Source # 
Show Duration Source # 
Generic Duration Source # 

Associated Types

type Rep Duration :: * -> * #

Methods

from :: Duration -> Rep Duration x #

to :: Rep Duration x -> Duration #

Hashable Duration Source # 

Methods

hashWithSalt :: Int -> Duration -> Int #

hash :: Duration -> Int #

FromJSON Duration Source # 
ToJSON Duration Source # 
NFData Duration Source # 

Methods

rnf :: Duration -> () #

ToQuery Duration Source # 
ToHeader Duration Source # 

Methods

toHeader :: HeaderName -> Duration -> [Header] #

ToByteString Duration Source # 

Methods

toBS :: Duration -> ByteString #

FromText Duration Source # 
ToText Duration Source # 

Methods

toText :: Duration -> Text #

type Rep Duration Source # 
type Rep Duration = D1 (MetaData "Duration" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) ((:+:) (C1 (MetaCons "Day14" PrefixI False) U1) (C1 (MetaCons "Day30" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Day7" PrefixI False) U1) (C1 (MetaCons "Hr24" PrefixI False) U1)))

Frequency

data Frequency Source #

Constructors

Daily 
Hourly 
Monthly 
Once 
Weekly 

Instances

Bounded Frequency Source # 
Enum Frequency Source # 
Eq Frequency Source # 
Data Frequency Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Frequency -> c Frequency #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Frequency #

toConstr :: Frequency -> Constr #

dataTypeOf :: Frequency -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Frequency) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Frequency) #

gmapT :: (forall b. Data b => b -> b) -> Frequency -> Frequency #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Frequency -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Frequency -> r #

gmapQ :: (forall d. Data d => d -> u) -> Frequency -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Frequency -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Frequency -> m Frequency #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Frequency -> m Frequency #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Frequency -> m Frequency #

Ord Frequency Source # 
Read Frequency Source # 
Show Frequency Source # 
Generic Frequency Source # 

Associated Types

type Rep Frequency :: * -> * #

Hashable Frequency Source # 
FromJSON Frequency Source # 
ToJSON Frequency Source # 
NFData Frequency Source # 

Methods

rnf :: Frequency -> () #

ToQuery Frequency Source # 
ToHeader Frequency Source # 
ToByteString Frequency Source # 

Methods

toBS :: Frequency -> ByteString #

FromText Frequency Source # 
ToText Frequency Source # 

Methods

toText :: Frequency -> Text #

type Rep Frequency Source # 
type Rep Frequency = D1 (MetaData "Frequency" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) ((:+:) (C1 (MetaCons "Daily" PrefixI False) U1) (C1 (MetaCons "Hourly" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Monthly" PrefixI False) U1) ((:+:) (C1 (MetaCons "Once" PrefixI False) U1) (C1 (MetaCons "Weekly" PrefixI False) U1))))

JobStatus

data JobStatus Source #

Instances

Bounded JobStatus Source # 
Enum JobStatus Source # 
Eq JobStatus Source # 
Data JobStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JobStatus -> c JobStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JobStatus #

toConstr :: JobStatus -> Constr #

dataTypeOf :: JobStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c JobStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JobStatus) #

gmapT :: (forall b. Data b => b -> b) -> JobStatus -> JobStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JobStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JobStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> JobStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JobStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JobStatus -> m JobStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JobStatus -> m JobStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JobStatus -> m JobStatus #

Ord JobStatus Source # 
Read JobStatus Source # 
Show JobStatus Source # 
Generic JobStatus Source # 

Associated Types

type Rep JobStatus :: * -> * #

Hashable JobStatus Source # 
FromJSON JobStatus Source # 
NFData JobStatus Source # 

Methods

rnf :: JobStatus -> () #

ToQuery JobStatus Source # 
ToHeader JobStatus Source # 
ToByteString JobStatus Source # 

Methods

toBS :: JobStatus -> ByteString #

FromText JobStatus Source # 
ToText JobStatus Source # 

Methods

toText :: JobStatus -> Text #

type Rep JobStatus Source # 
type Rep JobStatus = D1 (MetaData "JobStatus" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) ((:+:) (C1 (MetaCons "JSCompleted" PrefixI False) U1) ((:+:) (C1 (MetaCons "JSCompleting" PrefixI False) U1) (C1 (MetaCons "JSCreated" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "JSFailed" PrefixI False) U1) (C1 (MetaCons "JSFailing" PrefixI False) U1)) ((:+:) (C1 (MetaCons "JSInitializing" PrefixI False) U1) (C1 (MetaCons "JSProcessing" PrefixI False) U1))))

MessageType

data MessageType Source #

Constructors

Promotional 
Transactional 

Instances

Bounded MessageType Source # 
Enum MessageType Source # 
Eq MessageType Source # 
Data MessageType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageType -> c MessageType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageType #

toConstr :: MessageType -> Constr #

dataTypeOf :: MessageType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MessageType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageType) #

gmapT :: (forall b. Data b => b -> b) -> MessageType -> MessageType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageType -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageType -> m MessageType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageType -> m MessageType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageType -> m MessageType #

Ord MessageType Source # 
Read MessageType Source # 
Show MessageType Source # 
Generic MessageType Source # 

Associated Types

type Rep MessageType :: * -> * #

Hashable MessageType Source # 
FromJSON MessageType Source # 
ToJSON MessageType Source # 
NFData MessageType Source # 

Methods

rnf :: MessageType -> () #

ToQuery MessageType Source # 
ToHeader MessageType Source # 
ToByteString MessageType Source # 
FromText MessageType Source # 
ToText MessageType Source # 

Methods

toText :: MessageType -> Text #

type Rep MessageType Source # 
type Rep MessageType = D1 (MetaData "MessageType" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) (C1 (MetaCons "Promotional" PrefixI False) U1) (C1 (MetaCons "Transactional" PrefixI False) U1))

RecencyType

data RecencyType Source #

Constructors

Active 
Inactive 

Instances

Bounded RecencyType Source # 
Enum RecencyType Source # 
Eq RecencyType Source # 
Data RecencyType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecencyType -> c RecencyType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecencyType #

toConstr :: RecencyType -> Constr #

dataTypeOf :: RecencyType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RecencyType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecencyType) #

gmapT :: (forall b. Data b => b -> b) -> RecencyType -> RecencyType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecencyType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecencyType -> r #

gmapQ :: (forall d. Data d => d -> u) -> RecencyType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RecencyType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecencyType -> m RecencyType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecencyType -> m RecencyType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecencyType -> m RecencyType #

Ord RecencyType Source # 
Read RecencyType Source # 
Show RecencyType Source # 
Generic RecencyType Source # 

Associated Types

type Rep RecencyType :: * -> * #

Hashable RecencyType Source # 
FromJSON RecencyType Source # 
ToJSON RecencyType Source # 
NFData RecencyType Source # 

Methods

rnf :: RecencyType -> () #

ToQuery RecencyType Source # 
ToHeader RecencyType Source # 
ToByteString RecencyType Source # 
FromText RecencyType Source # 
ToText RecencyType Source # 

Methods

toText :: RecencyType -> Text #

type Rep RecencyType Source # 
type Rep RecencyType = D1 (MetaData "RecencyType" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) (C1 (MetaCons "Active" PrefixI False) U1) (C1 (MetaCons "Inactive" PrefixI False) U1))

SegmentType

data SegmentType Source #

Constructors

Dimensional 
Import 

Instances

Bounded SegmentType Source # 
Enum SegmentType Source # 
Eq SegmentType Source # 
Data SegmentType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SegmentType -> c SegmentType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SegmentType #

toConstr :: SegmentType -> Constr #

dataTypeOf :: SegmentType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SegmentType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SegmentType) #

gmapT :: (forall b. Data b => b -> b) -> SegmentType -> SegmentType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SegmentType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SegmentType -> r #

gmapQ :: (forall d. Data d => d -> u) -> SegmentType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SegmentType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SegmentType -> m SegmentType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentType -> m SegmentType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentType -> m SegmentType #

Ord SegmentType Source # 
Read SegmentType Source # 
Show SegmentType Source # 
Generic SegmentType Source # 

Associated Types

type Rep SegmentType :: * -> * #

Hashable SegmentType Source # 
FromJSON SegmentType Source # 
NFData SegmentType Source # 

Methods

rnf :: SegmentType -> () #

ToQuery SegmentType Source # 
ToHeader SegmentType Source # 
ToByteString SegmentType Source # 
FromText SegmentType Source # 
ToText SegmentType Source # 

Methods

toText :: SegmentType -> Text #

type Rep SegmentType Source # 
type Rep SegmentType = D1 (MetaData "SegmentType" "Network.AWS.Pinpoint.Types.Sum" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) ((:+:) (C1 (MetaCons "Dimensional" PrefixI False) U1) (C1 (MetaCons "Import" PrefixI False) U1))

ADMChannelRequest

data ADMChannelRequest Source #

Amazon Device Messaging channel definition.

See: aDMChannelRequest smart constructor.

Instances

Eq ADMChannelRequest Source # 
Data ADMChannelRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ADMChannelRequest -> c ADMChannelRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ADMChannelRequest #

toConstr :: ADMChannelRequest -> Constr #

dataTypeOf :: ADMChannelRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ADMChannelRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ADMChannelRequest) #

gmapT :: (forall b. Data b => b -> b) -> ADMChannelRequest -> ADMChannelRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ADMChannelRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ADMChannelRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> ADMChannelRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ADMChannelRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ADMChannelRequest -> m ADMChannelRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ADMChannelRequest -> m ADMChannelRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ADMChannelRequest -> m ADMChannelRequest #

Read ADMChannelRequest Source # 
Show ADMChannelRequest Source # 
Generic ADMChannelRequest Source # 
Hashable ADMChannelRequest Source # 
ToJSON ADMChannelRequest Source # 
NFData ADMChannelRequest Source # 

Methods

rnf :: ADMChannelRequest -> () #

type Rep ADMChannelRequest Source # 
type Rep ADMChannelRequest = D1 (MetaData "ADMChannelRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "ADMChannelRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_admcrClientId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_admcrClientSecret") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_admcrEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

aDMChannelRequest :: ADMChannelRequest Source #

Creates a value of ADMChannelRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

admcrClientId :: Lens' ADMChannelRequest (Maybe Text) Source #

Client ID as gotten from Amazon

admcrClientSecret :: Lens' ADMChannelRequest (Maybe Text) Source #

Client secret as gotten from Amazon

admcrEnabled :: Lens' ADMChannelRequest (Maybe Bool) Source #

If the channel is enabled for sending messages.

ADMChannelResponse

data ADMChannelResponse Source #

Amazon Device Messaging channel definition.

See: aDMChannelResponse smart constructor.

Instances

Eq ADMChannelResponse Source # 
Data ADMChannelResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ADMChannelResponse -> c ADMChannelResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ADMChannelResponse #

toConstr :: ADMChannelResponse -> Constr #

dataTypeOf :: ADMChannelResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ADMChannelResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ADMChannelResponse) #

gmapT :: (forall b. Data b => b -> b) -> ADMChannelResponse -> ADMChannelResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ADMChannelResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ADMChannelResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ADMChannelResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ADMChannelResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ADMChannelResponse -> m ADMChannelResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ADMChannelResponse -> m ADMChannelResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ADMChannelResponse -> m ADMChannelResponse #

Read ADMChannelResponse Source # 
Show ADMChannelResponse Source # 
Generic ADMChannelResponse Source # 
Hashable ADMChannelResponse Source # 
FromJSON ADMChannelResponse Source # 
NFData ADMChannelResponse Source # 

Methods

rnf :: ADMChannelResponse -> () #

type Rep ADMChannelResponse Source # 

aDMChannelResponse :: ADMChannelResponse Source #

Creates a value of ADMChannelResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

admcEnabled :: Lens' ADMChannelResponse (Maybe Bool) Source #

If the channel is enabled for sending messages.

admcId :: Lens' ADMChannelResponse (Maybe Text) Source #

Channel ID. Not used, only for backwards compatibility.

admcCreationDate :: Lens' ADMChannelResponse (Maybe Text) Source #

When was this segment created

admcLastModifiedBy :: Lens' ADMChannelResponse (Maybe Text) Source #

Who last updated this entry

admcHasCredential :: Lens' ADMChannelResponse (Maybe Bool) Source #

If the channel is registered with a credential for authentication.

ADMMessage

data ADMMessage Source #

ADM Message.

See: aDMMessage smart constructor.

Instances

Eq ADMMessage Source # 
Data ADMMessage Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ADMMessage -> c ADMMessage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ADMMessage #

toConstr :: ADMMessage -> Constr #

dataTypeOf :: ADMMessage -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ADMMessage) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ADMMessage) #

gmapT :: (forall b. Data b => b -> b) -> ADMMessage -> ADMMessage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ADMMessage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ADMMessage -> r #

gmapQ :: (forall d. Data d => d -> u) -> ADMMessage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ADMMessage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ADMMessage -> m ADMMessage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ADMMessage -> m ADMMessage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ADMMessage -> m ADMMessage #

Read ADMMessage Source # 
Show ADMMessage Source # 
Generic ADMMessage Source # 

Associated Types

type Rep ADMMessage :: * -> * #

Hashable ADMMessage Source # 
ToJSON ADMMessage Source # 
NFData ADMMessage Source # 

Methods

rnf :: ADMMessage -> () #

type Rep ADMMessage Source # 
type Rep ADMMessage = D1 (MetaData "ADMMessage" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "ADMMessage'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_admmSubstitutions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))) (S1 (MetaSel (Just Symbol "_admmExpiresAfter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_admmMD5") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_admmSilentPush") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_admmImageIconURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_admmRawContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_admmData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text)))) (S1 (MetaSel (Just Symbol "_admmSmallImageIconURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_admmBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_admmURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_admmSound") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_admmAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Action))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_admmImageURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_admmConsolidationKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_admmTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_admmIconReference") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

aDMMessage :: ADMMessage Source #

Creates a value of ADMMessage with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • admmSubstitutions - Default message substitutions. Can be overridden by individual address substitutions.
  • admmExpiresAfter - Optional. Number of seconds ADM should retain the message if the device is offline
  • admmMD5 - Optional. Base-64-encoded MD5 checksum of the data parameter. Used to verify data integrity
  • admmSilentPush - Indicates if the message should display on the users device. Silent pushes can be used for Remote Configuration and Phone Home use cases.
  • admmImageIconURL - The URL that points to an image used as the large icon to the notification content view.
  • admmRawContent - The Raw JSON formatted string to be used as the payload. This value overrides the message.
  • admmData - The data payload used for a silent push. This payload is added to the notifications' data.pinpoint.jsonBody' object
  • admmSmallImageIconURL - The URL that points to an image used as the small icon for the notification which will be used to represent the notification in the status bar and content view
  • admmBody - The message body of the notification, the email body or the text message.
  • admmURL - The URL to open in the user's mobile browser. Used if the value for Action is URL.
  • admmSound - Indicates a sound to play when the device receives the notification. Supports default, or the filename of a sound resource bundled in the app. Android sound files must reside in resraw/
  • admmAction - The action that occurs if the user taps a push notification delivered by the campaign: OPEN_APP - Your app launches, or it becomes the foreground app if it has been sent to the background. This is the default action. DEEP_LINK - Uses deep linking features in iOS and Android to open your app and display a designated user interface within the app. URL - The default mobile browser on the user's device launches and opens a web page at the URL you specify. Possible values include: OPEN_APP | DEEP_LINK | URL
  • admmImageURL - The URL that points to an image used in the push notification.
  • admmConsolidationKey - Optional. Arbitrary string used to indicate multiple messages are logically the same and that ADM is allowed to drop previously enqueued messages in favor of this one.
  • admmTitle - The message title that displays above the message on the user's device.
  • admmIconReference - The icon image name of the asset saved in your application.

admmSubstitutions :: Lens' ADMMessage (HashMap Text [Text]) Source #

Default message substitutions. Can be overridden by individual address substitutions.

admmExpiresAfter :: Lens' ADMMessage (Maybe Text) Source #

Optional. Number of seconds ADM should retain the message if the device is offline

admmMD5 :: Lens' ADMMessage (Maybe Text) Source #

Optional. Base-64-encoded MD5 checksum of the data parameter. Used to verify data integrity

admmSilentPush :: Lens' ADMMessage (Maybe Bool) Source #

Indicates if the message should display on the users device. Silent pushes can be used for Remote Configuration and Phone Home use cases.

admmImageIconURL :: Lens' ADMMessage (Maybe Text) Source #

The URL that points to an image used as the large icon to the notification content view.

admmRawContent :: Lens' ADMMessage (Maybe Text) Source #

The Raw JSON formatted string to be used as the payload. This value overrides the message.

admmData :: Lens' ADMMessage (HashMap Text Text) Source #

The data payload used for a silent push. This payload is added to the notifications' data.pinpoint.jsonBody' object

admmSmallImageIconURL :: Lens' ADMMessage (Maybe Text) Source #

The URL that points to an image used as the small icon for the notification which will be used to represent the notification in the status bar and content view

admmBody :: Lens' ADMMessage (Maybe Text) Source #

The message body of the notification, the email body or the text message.

admmURL :: Lens' ADMMessage (Maybe Text) Source #

The URL to open in the user's mobile browser. Used if the value for Action is URL.

admmSound :: Lens' ADMMessage (Maybe Text) Source #

Indicates a sound to play when the device receives the notification. Supports default, or the filename of a sound resource bundled in the app. Android sound files must reside in resraw/

admmAction :: Lens' ADMMessage (Maybe Action) Source #

The action that occurs if the user taps a push notification delivered by the campaign: OPEN_APP - Your app launches, or it becomes the foreground app if it has been sent to the background. This is the default action. DEEP_LINK - Uses deep linking features in iOS and Android to open your app and display a designated user interface within the app. URL - The default mobile browser on the user's device launches and opens a web page at the URL you specify. Possible values include: OPEN_APP | DEEP_LINK | URL

admmImageURL :: Lens' ADMMessage (Maybe Text) Source #

The URL that points to an image used in the push notification.

admmConsolidationKey :: Lens' ADMMessage (Maybe Text) Source #

Optional. Arbitrary string used to indicate multiple messages are logically the same and that ADM is allowed to drop previously enqueued messages in favor of this one.

admmTitle :: Lens' ADMMessage (Maybe Text) Source #

The message title that displays above the message on the user's device.

admmIconReference :: Lens' ADMMessage (Maybe Text) Source #

The icon image name of the asset saved in your application.

APNSChannelRequest

data APNSChannelRequest Source #

Apple Push Notification Service channel definition.

See: apnsChannelRequest smart constructor.

Instances

Eq APNSChannelRequest Source # 
Data APNSChannelRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> APNSChannelRequest -> c APNSChannelRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c APNSChannelRequest #

toConstr :: APNSChannelRequest -> Constr #

dataTypeOf :: APNSChannelRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c APNSChannelRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c APNSChannelRequest) #

gmapT :: (forall b. Data b => b -> b) -> APNSChannelRequest -> APNSChannelRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> APNSChannelRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> APNSChannelRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> APNSChannelRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> APNSChannelRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> APNSChannelRequest -> m APNSChannelRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSChannelRequest -> m APNSChannelRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSChannelRequest -> m APNSChannelRequest #

Read APNSChannelRequest Source # 
Show APNSChannelRequest Source # 
Generic APNSChannelRequest Source # 
Hashable APNSChannelRequest Source # 
ToJSON APNSChannelRequest Source # 
NFData APNSChannelRequest Source # 

Methods

rnf :: APNSChannelRequest -> () #

type Rep APNSChannelRequest Source # 
type Rep APNSChannelRequest = D1 (MetaData "APNSChannelRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "APNSChannelRequest'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_acrTokenKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_acrPrivateKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_acrEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_acrTeamId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_acrBundleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_acrDefaultAuthenticationMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_acrCertificate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_acrTokenKeyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

apnsChannelRequest :: APNSChannelRequest Source #

Creates a value of APNSChannelRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

acrTokenKey :: Lens' APNSChannelRequest (Maybe Text) Source #

The token key used for APNs Tokens.

acrPrivateKey :: Lens' APNSChannelRequest (Maybe Text) Source #

The certificate private key.

acrEnabled :: Lens' APNSChannelRequest (Maybe Bool) Source #

If the channel is enabled for sending messages.

acrTeamId :: Lens' APNSChannelRequest (Maybe Text) Source #

The team id used for APNs Tokens.

acrBundleId :: Lens' APNSChannelRequest (Maybe Text) Source #

The bundle id used for APNs Tokens.

acrDefaultAuthenticationMethod :: Lens' APNSChannelRequest (Maybe Text) Source #

The default authentication method used for APNs.

acrCertificate :: Lens' APNSChannelRequest (Maybe Text) Source #

The distribution certificate from Apple.

acrTokenKeyId :: Lens' APNSChannelRequest (Maybe Text) Source #

The token key used for APNs Tokens.

APNSChannelResponse

data APNSChannelResponse Source #

Apple Distribution Push Notification Service channel definition.

See: apnsChannelResponse smart constructor.

Instances

Eq APNSChannelResponse Source # 
Data APNSChannelResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> APNSChannelResponse -> c APNSChannelResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c APNSChannelResponse #

toConstr :: APNSChannelResponse -> Constr #

dataTypeOf :: APNSChannelResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c APNSChannelResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c APNSChannelResponse) #

gmapT :: (forall b. Data b => b -> b) -> APNSChannelResponse -> APNSChannelResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> APNSChannelResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> APNSChannelResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> APNSChannelResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> APNSChannelResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> APNSChannelResponse -> m APNSChannelResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSChannelResponse -> m APNSChannelResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSChannelResponse -> m APNSChannelResponse #

Read APNSChannelResponse Source # 
Show APNSChannelResponse Source # 
Generic APNSChannelResponse Source # 
Hashable APNSChannelResponse Source # 
FromJSON APNSChannelResponse Source # 
NFData APNSChannelResponse Source # 

Methods

rnf :: APNSChannelResponse -> () #

type Rep APNSChannelResponse Source # 
type Rep APNSChannelResponse = D1 (MetaData "APNSChannelResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "APNSChannelResponse'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_acPlatform") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_acLastModifiedDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_acEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "_acHasTokenKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_acDefaultAuthenticationMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_acIsArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_acApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_acVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_acId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_acCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_acLastModifiedBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_acHasCredential") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))))

apnsChannelResponse :: APNSChannelResponse Source #

Creates a value of APNSChannelResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

acPlatform :: Lens' APNSChannelResponse (Maybe Text) Source #

The platform type. Will be APNS.

acEnabled :: Lens' APNSChannelResponse (Maybe Bool) Source #

If the channel is enabled for sending messages.

acHasTokenKey :: Lens' APNSChannelResponse (Maybe Bool) Source #

If the channel is registered with a token key for authentication.

acDefaultAuthenticationMethod :: Lens' APNSChannelResponse (Maybe Text) Source #

The default authentication method used for APNs.

acIsArchived :: Lens' APNSChannelResponse (Maybe Bool) Source #

Is this channel archived

acApplicationId :: Lens' APNSChannelResponse (Maybe Text) Source #

The ID of the application to which the channel applies.

acId :: Lens' APNSChannelResponse (Maybe Text) Source #

Channel ID. Not used. Present only for backwards compatibility.

acCreationDate :: Lens' APNSChannelResponse (Maybe Text) Source #

When was this segment created

acLastModifiedBy :: Lens' APNSChannelResponse (Maybe Text) Source #

Who last updated this entry

acHasCredential :: Lens' APNSChannelResponse (Maybe Bool) Source #

If the channel is registered with a credential for authentication.

APNSMessage

data APNSMessage Source #

APNS Message.

See: apnsMessage smart constructor.

Instances

Eq APNSMessage Source # 
Data APNSMessage Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> APNSMessage -> c APNSMessage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c APNSMessage #

toConstr :: APNSMessage -> Constr #

dataTypeOf :: APNSMessage -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c APNSMessage) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c APNSMessage) #

gmapT :: (forall b. Data b => b -> b) -> APNSMessage -> APNSMessage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> APNSMessage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> APNSMessage -> r #

gmapQ :: (forall d. Data d => d -> u) -> APNSMessage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> APNSMessage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> APNSMessage -> m APNSMessage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSMessage -> m APNSMessage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSMessage -> m APNSMessage #

Read APNSMessage Source # 
Show APNSMessage Source # 
Generic APNSMessage Source # 

Associated Types

type Rep APNSMessage :: * -> * #

Hashable APNSMessage Source # 
ToJSON APNSMessage Source # 
NFData APNSMessage Source # 

Methods

rnf :: APNSMessage -> () #

type Rep APNSMessage Source # 
type Rep APNSMessage = D1 (MetaData "APNSMessage" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "APNSMessage'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_amSubstitutions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))) (S1 (MetaSel (Just Symbol "_amSilentPush") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_amPriority") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_amRawContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_amData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text)))) (S1 (MetaSel (Just Symbol "_amBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_amCategory") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_amTimeToLive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_amURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_amSound") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_amAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Action))) (S1 (MetaSel (Just Symbol "_amMediaURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_amPreferredAuthenticationMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_amBadge") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))) ((:*:) (S1 (MetaSel (Just Symbol "_amTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_amThreadId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_amCollapseId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))))

apnsMessage :: APNSMessage Source #

Creates a value of APNSMessage with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • amSubstitutions - Default message substitutions. Can be overridden by individual address substitutions.
  • amSilentPush - Indicates if the message should display on the users device. Silent pushes can be used for Remote Configuration and Phone Home use cases.
  • amPriority - Is this a transaction priority message or lower priority.
  • amRawContent - The Raw JSON formatted string to be used as the payload. This value overrides the message.
  • amData - The data payload used for a silent push. This payload is added to the notifications' data.pinpoint.jsonBody' object
  • amBody - The message body of the notification, the email body or the text message.
  • amCategory - Provide this key with a string value that represents the notification's type. This value corresponds to the value in the identifier property of one of your app's registered categories.
  • amTimeToLive - This parameter specifies how long (in seconds) the message should be kept if APNS is unable to deliver the notification the first time. If the value is 0, APNS treats the notification as if it expires immediately and does not store the notification or attempt to redeliver it. This value is converted to the expiration field when sent to APNS
  • amURL - The URL to open in the user's mobile browser. Used if the value for Action is URL.
  • amSound - Include this key when you want the system to play a sound. The value of this key is the name of a sound file in your app's main bundle or in the Library/Sounds folder of your app's data container. If the sound file cannot be found, or if you specify defaultfor the value, the system plays the default alert sound.
  • amAction - The action that occurs if the user taps a push notification delivered by the campaign: OPEN_APP - Your app launches, or it becomes the foreground app if it has been sent to the background. This is the default action. DEEP_LINK - Uses deep linking features in iOS and Android to open your app and display a designated user interface within the app. URL - The default mobile browser on the user's device launches and opens a web page at the URL you specify. Possible values include: OPEN_APP | DEEP_LINK | URL
  • amMediaURL - The URL that points to a video used in the push notification.
  • amPreferredAuthenticationMethod - The preferred authentication method, either CERTIFICATE or TOKEN
  • amBadge - Include this key when you want the system to modify the badge of your app icon. If this key is not included in the dictionary, the badge is not changed. To remove the badge, set the value of this key to 0.
  • amTitle - The message title that displays above the message on the user's device.
  • amThreadId - Provide this key with a string value that represents the app-specific identifier for grouping notifications. If you provide a Notification Content app extension, you can use this value to group your notifications together.
  • amCollapseId - Multiple notifications with the same collapse identifier are displayed to the user as a single notification. The value of this key must not exceed 64 bytes.

amSubstitutions :: Lens' APNSMessage (HashMap Text [Text]) Source #

Default message substitutions. Can be overridden by individual address substitutions.

amSilentPush :: Lens' APNSMessage (Maybe Bool) Source #

Indicates if the message should display on the users device. Silent pushes can be used for Remote Configuration and Phone Home use cases.

amPriority :: Lens' APNSMessage (Maybe Text) Source #

Is this a transaction priority message or lower priority.

amRawContent :: Lens' APNSMessage (Maybe Text) Source #

The Raw JSON formatted string to be used as the payload. This value overrides the message.

amData :: Lens' APNSMessage (HashMap Text Text) Source #

The data payload used for a silent push. This payload is added to the notifications' data.pinpoint.jsonBody' object

amBody :: Lens' APNSMessage (Maybe Text) Source #

The message body of the notification, the email body or the text message.

amCategory :: Lens' APNSMessage (Maybe Text) Source #

Provide this key with a string value that represents the notification's type. This value corresponds to the value in the identifier property of one of your app's registered categories.

amTimeToLive :: Lens' APNSMessage (Maybe Int) Source #

This parameter specifies how long (in seconds) the message should be kept if APNS is unable to deliver the notification the first time. If the value is 0, APNS treats the notification as if it expires immediately and does not store the notification or attempt to redeliver it. This value is converted to the expiration field when sent to APNS

amURL :: Lens' APNSMessage (Maybe Text) Source #

The URL to open in the user's mobile browser. Used if the value for Action is URL.

amSound :: Lens' APNSMessage (Maybe Text) Source #

Include this key when you want the system to play a sound. The value of this key is the name of a sound file in your app's main bundle or in the Library/Sounds folder of your app's data container. If the sound file cannot be found, or if you specify defaultfor the value, the system plays the default alert sound.

amAction :: Lens' APNSMessage (Maybe Action) Source #

The action that occurs if the user taps a push notification delivered by the campaign: OPEN_APP - Your app launches, or it becomes the foreground app if it has been sent to the background. This is the default action. DEEP_LINK - Uses deep linking features in iOS and Android to open your app and display a designated user interface within the app. URL - The default mobile browser on the user's device launches and opens a web page at the URL you specify. Possible values include: OPEN_APP | DEEP_LINK | URL

amMediaURL :: Lens' APNSMessage (Maybe Text) Source #

The URL that points to a video used in the push notification.

amPreferredAuthenticationMethod :: Lens' APNSMessage (Maybe Text) Source #

The preferred authentication method, either CERTIFICATE or TOKEN

amBadge :: Lens' APNSMessage (Maybe Int) Source #

Include this key when you want the system to modify the badge of your app icon. If this key is not included in the dictionary, the badge is not changed. To remove the badge, set the value of this key to 0.

amTitle :: Lens' APNSMessage (Maybe Text) Source #

The message title that displays above the message on the user's device.

amThreadId :: Lens' APNSMessage (Maybe Text) Source #

Provide this key with a string value that represents the app-specific identifier for grouping notifications. If you provide a Notification Content app extension, you can use this value to group your notifications together.

amCollapseId :: Lens' APNSMessage (Maybe Text) Source #

Multiple notifications with the same collapse identifier are displayed to the user as a single notification. The value of this key must not exceed 64 bytes.

APNSSandboxChannelRequest

data APNSSandboxChannelRequest Source #

Apple Development Push Notification Service channel definition.

See: apnsSandboxChannelRequest smart constructor.

Instances

Eq APNSSandboxChannelRequest Source # 
Data APNSSandboxChannelRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> APNSSandboxChannelRequest -> c APNSSandboxChannelRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c APNSSandboxChannelRequest #

toConstr :: APNSSandboxChannelRequest -> Constr #

dataTypeOf :: APNSSandboxChannelRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c APNSSandboxChannelRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c APNSSandboxChannelRequest) #

gmapT :: (forall b. Data b => b -> b) -> APNSSandboxChannelRequest -> APNSSandboxChannelRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> APNSSandboxChannelRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> APNSSandboxChannelRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> APNSSandboxChannelRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> APNSSandboxChannelRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> APNSSandboxChannelRequest -> m APNSSandboxChannelRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSSandboxChannelRequest -> m APNSSandboxChannelRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSSandboxChannelRequest -> m APNSSandboxChannelRequest #

Read APNSSandboxChannelRequest Source # 
Show APNSSandboxChannelRequest Source # 
Generic APNSSandboxChannelRequest Source # 
Hashable APNSSandboxChannelRequest Source # 
ToJSON APNSSandboxChannelRequest Source # 
NFData APNSSandboxChannelRequest Source # 
type Rep APNSSandboxChannelRequest Source # 
type Rep APNSSandboxChannelRequest = D1 (MetaData "APNSSandboxChannelRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "APNSSandboxChannelRequest'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ascrTokenKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ascrPrivateKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ascrEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_ascrTeamId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ascrBundleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ascrDefaultAuthenticationMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ascrCertificate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ascrTokenKeyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

apnsSandboxChannelRequest :: APNSSandboxChannelRequest Source #

Creates a value of APNSSandboxChannelRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ascrTokenKey :: Lens' APNSSandboxChannelRequest (Maybe Text) Source #

The token key used for APNs Tokens.

ascrEnabled :: Lens' APNSSandboxChannelRequest (Maybe Bool) Source #

If the channel is enabled for sending messages.

ascrTeamId :: Lens' APNSSandboxChannelRequest (Maybe Text) Source #

The team id used for APNs Tokens.

ascrBundleId :: Lens' APNSSandboxChannelRequest (Maybe Text) Source #

The bundle id used for APNs Tokens.

ascrDefaultAuthenticationMethod :: Lens' APNSSandboxChannelRequest (Maybe Text) Source #

The default authentication method used for APNs.

ascrCertificate :: Lens' APNSSandboxChannelRequest (Maybe Text) Source #

The distribution certificate from Apple.

ascrTokenKeyId :: Lens' APNSSandboxChannelRequest (Maybe Text) Source #

The token key used for APNs Tokens.

APNSSandboxChannelResponse

data APNSSandboxChannelResponse Source #

Apple Development Push Notification Service channel definition.

See: apnsSandboxChannelResponse smart constructor.

Instances

Eq APNSSandboxChannelResponse Source # 
Data APNSSandboxChannelResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> APNSSandboxChannelResponse -> c APNSSandboxChannelResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c APNSSandboxChannelResponse #

toConstr :: APNSSandboxChannelResponse -> Constr #

dataTypeOf :: APNSSandboxChannelResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c APNSSandboxChannelResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c APNSSandboxChannelResponse) #

gmapT :: (forall b. Data b => b -> b) -> APNSSandboxChannelResponse -> APNSSandboxChannelResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> APNSSandboxChannelResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> APNSSandboxChannelResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> APNSSandboxChannelResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> APNSSandboxChannelResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> APNSSandboxChannelResponse -> m APNSSandboxChannelResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSSandboxChannelResponse -> m APNSSandboxChannelResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSSandboxChannelResponse -> m APNSSandboxChannelResponse #

Read APNSSandboxChannelResponse Source # 
Show APNSSandboxChannelResponse Source # 
Generic APNSSandboxChannelResponse Source # 
Hashable APNSSandboxChannelResponse Source # 
FromJSON APNSSandboxChannelResponse Source # 
NFData APNSSandboxChannelResponse Source # 
type Rep APNSSandboxChannelResponse Source # 
type Rep APNSSandboxChannelResponse = D1 (MetaData "APNSSandboxChannelResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "APNSSandboxChannelResponse'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ascPlatform") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ascLastModifiedDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ascEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "_ascHasTokenKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_ascDefaultAuthenticationMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ascIsArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ascApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ascVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_ascId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_ascCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ascLastModifiedBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ascHasCredential") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))))

apnsSandboxChannelResponse :: APNSSandboxChannelResponse Source #

Creates a value of APNSSandboxChannelResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ascPlatform :: Lens' APNSSandboxChannelResponse (Maybe Text) Source #

The platform type. Will be APNS_SANDBOX.

ascEnabled :: Lens' APNSSandboxChannelResponse (Maybe Bool) Source #

If the channel is enabled for sending messages.

ascHasTokenKey :: Lens' APNSSandboxChannelResponse (Maybe Bool) Source #

If the channel is registered with a token key for authentication.

ascDefaultAuthenticationMethod :: Lens' APNSSandboxChannelResponse (Maybe Text) Source #

The default authentication method used for APNs.

ascId :: Lens' APNSSandboxChannelResponse (Maybe Text) Source #

Channel ID. Not used, only for backwards compatibility.

ascHasCredential :: Lens' APNSSandboxChannelResponse (Maybe Bool) Source #

If the channel is registered with a credential for authentication.

APNSVoipChannelRequest

data APNSVoipChannelRequest Source #

Apple VoIP Push Notification Service channel definition.

See: apnsVoipChannelRequest smart constructor.

Instances

Eq APNSVoipChannelRequest Source # 
Data APNSVoipChannelRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> APNSVoipChannelRequest -> c APNSVoipChannelRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c APNSVoipChannelRequest #

toConstr :: APNSVoipChannelRequest -> Constr #

dataTypeOf :: APNSVoipChannelRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c APNSVoipChannelRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c APNSVoipChannelRequest) #

gmapT :: (forall b. Data b => b -> b) -> APNSVoipChannelRequest -> APNSVoipChannelRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> APNSVoipChannelRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> APNSVoipChannelRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> APNSVoipChannelRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> APNSVoipChannelRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> APNSVoipChannelRequest -> m APNSVoipChannelRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSVoipChannelRequest -> m APNSVoipChannelRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSVoipChannelRequest -> m APNSVoipChannelRequest #

Read APNSVoipChannelRequest Source # 
Show APNSVoipChannelRequest Source # 
Generic APNSVoipChannelRequest Source # 
Hashable APNSVoipChannelRequest Source # 
ToJSON APNSVoipChannelRequest Source # 
NFData APNSVoipChannelRequest Source # 

Methods

rnf :: APNSVoipChannelRequest -> () #

type Rep APNSVoipChannelRequest Source # 
type Rep APNSVoipChannelRequest = D1 (MetaData "APNSVoipChannelRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "APNSVoipChannelRequest'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_avcrTokenKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_avcrPrivateKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_avcrEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_avcrTeamId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_avcrBundleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_avcrDefaultAuthenticationMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_avcrCertificate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_avcrTokenKeyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

apnsVoipChannelRequest :: APNSVoipChannelRequest Source #

Creates a value of APNSVoipChannelRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

avcrTokenKey :: Lens' APNSVoipChannelRequest (Maybe Text) Source #

The token key used for APNs Tokens.

avcrPrivateKey :: Lens' APNSVoipChannelRequest (Maybe Text) Source #

The certificate private key.

avcrEnabled :: Lens' APNSVoipChannelRequest (Maybe Bool) Source #

If the channel is enabled for sending messages.

avcrTeamId :: Lens' APNSVoipChannelRequest (Maybe Text) Source #

The team id used for APNs Tokens.

avcrBundleId :: Lens' APNSVoipChannelRequest (Maybe Text) Source #

The bundle id used for APNs Tokens.

avcrDefaultAuthenticationMethod :: Lens' APNSVoipChannelRequest (Maybe Text) Source #

The default authentication method used for APNs.

avcrCertificate :: Lens' APNSVoipChannelRequest (Maybe Text) Source #

The distribution certificate from Apple.

avcrTokenKeyId :: Lens' APNSVoipChannelRequest (Maybe Text) Source #

The token key used for APNs Tokens.

APNSVoipChannelResponse

data APNSVoipChannelResponse Source #

Apple VoIP Push Notification Service channel definition.

See: apnsVoipChannelResponse smart constructor.

Instances

Eq APNSVoipChannelResponse Source # 
Data APNSVoipChannelResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> APNSVoipChannelResponse -> c APNSVoipChannelResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c APNSVoipChannelResponse #

toConstr :: APNSVoipChannelResponse -> Constr #

dataTypeOf :: APNSVoipChannelResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c APNSVoipChannelResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c APNSVoipChannelResponse) #

gmapT :: (forall b. Data b => b -> b) -> APNSVoipChannelResponse -> APNSVoipChannelResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> APNSVoipChannelResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> APNSVoipChannelResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> APNSVoipChannelResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> APNSVoipChannelResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> APNSVoipChannelResponse -> m APNSVoipChannelResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSVoipChannelResponse -> m APNSVoipChannelResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSVoipChannelResponse -> m APNSVoipChannelResponse #

Read APNSVoipChannelResponse Source # 
Show APNSVoipChannelResponse Source # 
Generic APNSVoipChannelResponse Source # 
Hashable APNSVoipChannelResponse Source # 
FromJSON APNSVoipChannelResponse Source # 
NFData APNSVoipChannelResponse Source # 

Methods

rnf :: APNSVoipChannelResponse -> () #

type Rep APNSVoipChannelResponse Source # 
type Rep APNSVoipChannelResponse = D1 (MetaData "APNSVoipChannelResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "APNSVoipChannelResponse'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_avcPlatform") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_avcLastModifiedDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_avcEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "_avcHasTokenKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_avcDefaultAuthenticationMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_avcIsArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_avcApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_avcVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_avcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_avcCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_avcLastModifiedBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_avcHasCredential") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))))

apnsVoipChannelResponse :: APNSVoipChannelResponse Source #

Creates a value of APNSVoipChannelResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

avcPlatform :: Lens' APNSVoipChannelResponse (Maybe Text) Source #

The platform type. Will be APNS.

avcEnabled :: Lens' APNSVoipChannelResponse (Maybe Bool) Source #

If the channel is enabled for sending messages.

avcHasTokenKey :: Lens' APNSVoipChannelResponse (Maybe Bool) Source #

If the channel is registered with a token key for authentication.

avcDefaultAuthenticationMethod :: Lens' APNSVoipChannelResponse (Maybe Text) Source #

The default authentication method used for APNs.

avcId :: Lens' APNSVoipChannelResponse (Maybe Text) Source #

Channel ID. Not used, only for backwards compatibility.

avcCreationDate :: Lens' APNSVoipChannelResponse (Maybe Text) Source #

When was this segment created

avcHasCredential :: Lens' APNSVoipChannelResponse (Maybe Bool) Source #

If the channel is registered with a credential for authentication.

APNSVoipSandboxChannelRequest

data APNSVoipSandboxChannelRequest Source #

Apple VoIP Developer Push Notification Service channel definition.

See: apnsVoipSandboxChannelRequest smart constructor.

Instances

Eq APNSVoipSandboxChannelRequest Source # 
Data APNSVoipSandboxChannelRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> APNSVoipSandboxChannelRequest -> c APNSVoipSandboxChannelRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c APNSVoipSandboxChannelRequest #

toConstr :: APNSVoipSandboxChannelRequest -> Constr #

dataTypeOf :: APNSVoipSandboxChannelRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c APNSVoipSandboxChannelRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c APNSVoipSandboxChannelRequest) #

gmapT :: (forall b. Data b => b -> b) -> APNSVoipSandboxChannelRequest -> APNSVoipSandboxChannelRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> APNSVoipSandboxChannelRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> APNSVoipSandboxChannelRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> APNSVoipSandboxChannelRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> APNSVoipSandboxChannelRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> APNSVoipSandboxChannelRequest -> m APNSVoipSandboxChannelRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSVoipSandboxChannelRequest -> m APNSVoipSandboxChannelRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSVoipSandboxChannelRequest -> m APNSVoipSandboxChannelRequest #

Read APNSVoipSandboxChannelRequest Source # 
Show APNSVoipSandboxChannelRequest Source # 
Generic APNSVoipSandboxChannelRequest Source # 
Hashable APNSVoipSandboxChannelRequest Source # 
ToJSON APNSVoipSandboxChannelRequest Source # 
NFData APNSVoipSandboxChannelRequest Source # 
type Rep APNSVoipSandboxChannelRequest Source # 
type Rep APNSVoipSandboxChannelRequest = D1 (MetaData "APNSVoipSandboxChannelRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "APNSVoipSandboxChannelRequest'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_avscrTokenKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_avscrPrivateKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_avscrEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_avscrTeamId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_avscrBundleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_avscrDefaultAuthenticationMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_avscrCertificate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_avscrTokenKeyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

apnsVoipSandboxChannelRequest :: APNSVoipSandboxChannelRequest Source #

Creates a value of APNSVoipSandboxChannelRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

avscrTokenKey :: Lens' APNSVoipSandboxChannelRequest (Maybe Text) Source #

The token key used for APNs Tokens.

avscrEnabled :: Lens' APNSVoipSandboxChannelRequest (Maybe Bool) Source #

If the channel is enabled for sending messages.

avscrTeamId :: Lens' APNSVoipSandboxChannelRequest (Maybe Text) Source #

The team id used for APNs Tokens.

avscrBundleId :: Lens' APNSVoipSandboxChannelRequest (Maybe Text) Source #

The bundle id used for APNs Tokens.

avscrDefaultAuthenticationMethod :: Lens' APNSVoipSandboxChannelRequest (Maybe Text) Source #

The default authentication method used for APNs.

avscrCertificate :: Lens' APNSVoipSandboxChannelRequest (Maybe Text) Source #

The distribution certificate from Apple.

avscrTokenKeyId :: Lens' APNSVoipSandboxChannelRequest (Maybe Text) Source #

The token key used for APNs Tokens.

APNSVoipSandboxChannelResponse

data APNSVoipSandboxChannelResponse Source #

Apple VoIP Developer Push Notification Service channel definition.

See: apnsVoipSandboxChannelResponse smart constructor.

Instances

Eq APNSVoipSandboxChannelResponse Source # 
Data APNSVoipSandboxChannelResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> APNSVoipSandboxChannelResponse -> c APNSVoipSandboxChannelResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c APNSVoipSandboxChannelResponse #

toConstr :: APNSVoipSandboxChannelResponse -> Constr #

dataTypeOf :: APNSVoipSandboxChannelResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c APNSVoipSandboxChannelResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c APNSVoipSandboxChannelResponse) #

gmapT :: (forall b. Data b => b -> b) -> APNSVoipSandboxChannelResponse -> APNSVoipSandboxChannelResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> APNSVoipSandboxChannelResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> APNSVoipSandboxChannelResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> APNSVoipSandboxChannelResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> APNSVoipSandboxChannelResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> APNSVoipSandboxChannelResponse -> m APNSVoipSandboxChannelResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSVoipSandboxChannelResponse -> m APNSVoipSandboxChannelResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> APNSVoipSandboxChannelResponse -> m APNSVoipSandboxChannelResponse #

Read APNSVoipSandboxChannelResponse Source # 
Show APNSVoipSandboxChannelResponse Source # 
Generic APNSVoipSandboxChannelResponse Source # 
Hashable APNSVoipSandboxChannelResponse Source # 
FromJSON APNSVoipSandboxChannelResponse Source # 
NFData APNSVoipSandboxChannelResponse Source # 
type Rep APNSVoipSandboxChannelResponse Source # 
type Rep APNSVoipSandboxChannelResponse = D1 (MetaData "APNSVoipSandboxChannelResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "APNSVoipSandboxChannelResponse'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_avscPlatform") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_avscLastModifiedDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_avscEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "_avscHasTokenKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_avscDefaultAuthenticationMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_avscIsArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_avscApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_avscVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_avscId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_avscCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_avscLastModifiedBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_avscHasCredential") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))))

apnsVoipSandboxChannelResponse :: APNSVoipSandboxChannelResponse Source #

Creates a value of APNSVoipSandboxChannelResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

avscPlatform :: Lens' APNSVoipSandboxChannelResponse (Maybe Text) Source #

The platform type. Will be APNS.

avscEnabled :: Lens' APNSVoipSandboxChannelResponse (Maybe Bool) Source #

If the channel is enabled for sending messages.

avscHasTokenKey :: Lens' APNSVoipSandboxChannelResponse (Maybe Bool) Source #

If the channel is registered with a token key for authentication.

avscDefaultAuthenticationMethod :: Lens' APNSVoipSandboxChannelResponse (Maybe Text) Source #

The default authentication method used for APNs.

avscId :: Lens' APNSVoipSandboxChannelResponse (Maybe Text) Source #

Channel ID. Not used, only for backwards compatibility.

avscHasCredential :: Lens' APNSVoipSandboxChannelResponse (Maybe Bool) Source #

If the channel is registered with a credential for authentication.

ActivitiesResponse

data ActivitiesResponse Source #

Activities for campaign.

See: activitiesResponse smart constructor.

Instances

Eq ActivitiesResponse Source # 
Data ActivitiesResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ActivitiesResponse -> c ActivitiesResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ActivitiesResponse #

toConstr :: ActivitiesResponse -> Constr #

dataTypeOf :: ActivitiesResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ActivitiesResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ActivitiesResponse) #

gmapT :: (forall b. Data b => b -> b) -> ActivitiesResponse -> ActivitiesResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ActivitiesResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ActivitiesResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ActivitiesResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ActivitiesResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ActivitiesResponse -> m ActivitiesResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ActivitiesResponse -> m ActivitiesResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ActivitiesResponse -> m ActivitiesResponse #

Read ActivitiesResponse Source # 
Show ActivitiesResponse Source # 
Generic ActivitiesResponse Source # 
Hashable ActivitiesResponse Source # 
FromJSON ActivitiesResponse Source # 
NFData ActivitiesResponse Source # 

Methods

rnf :: ActivitiesResponse -> () #

type Rep ActivitiesResponse Source # 
type Rep ActivitiesResponse = D1 (MetaData "ActivitiesResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" True) (C1 (MetaCons "ActivitiesResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_aItem") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [ActivityResponse]))))

activitiesResponse :: ActivitiesResponse Source #

Creates a value of ActivitiesResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • aItem - List of campaign activities

aItem :: Lens' ActivitiesResponse [ActivityResponse] Source #

List of campaign activities

ActivityResponse

data ActivityResponse Source #

Activity definition

See: activityResponse smart constructor.

Instances

Eq ActivityResponse Source # 
Data ActivityResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ActivityResponse -> c ActivityResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ActivityResponse #

toConstr :: ActivityResponse -> Constr #

dataTypeOf :: ActivityResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ActivityResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ActivityResponse) #

gmapT :: (forall b. Data b => b -> b) -> ActivityResponse -> ActivityResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ActivityResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ActivityResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ActivityResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ActivityResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ActivityResponse -> m ActivityResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ActivityResponse -> m ActivityResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ActivityResponse -> m ActivityResponse #

Read ActivityResponse Source # 
Show ActivityResponse Source # 
Generic ActivityResponse Source # 
Hashable ActivityResponse Source # 
FromJSON ActivityResponse Source # 
NFData ActivityResponse Source # 

Methods

rnf :: ActivityResponse -> () #

type Rep ActivityResponse Source # 
type Rep ActivityResponse = D1 (MetaData "ActivityResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "ActivityResponse'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_aStart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aCampaignId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_aTimezonesCompletedCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) ((:*:) (S1 (MetaSel (Just Symbol "_aTimezonesTotalCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_aResult") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aTreatmentId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_aSuccessfulEndpointCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_aEnd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aTotalEndpointCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))) ((:*:) (S1 (MetaSel (Just Symbol "_aId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aScheduledStart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

activityResponse :: ActivityResponse Source #

Creates a value of ActivityResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • aState - The state of the activity. Valid values: PENDING, INITIALIZING, RUNNING, PAUSED, CANCELLED, COMPLETED
  • aStart - The actual start time of the activity in ISO 8601 format.
  • aCampaignId - The ID of the campaign to which the activity applies.
  • aTimezonesCompletedCount - The total number of timezones completed.
  • aTimezonesTotalCount - The total number of unique timezones present in the segment.
  • aResult - Indicates whether the activity succeeded. Valid values: SUCCESS, FAIL
  • aTreatmentId - The ID of a variation of the campaign used for A/B testing.
  • aSuccessfulEndpointCount - The total number of endpoints to which the campaign successfully delivered messages.
  • aEnd - The actual time the activity was marked CANCELLED or COMPLETED. Provided in ISO 8601 format.
  • aApplicationId - The ID of the application to which the campaign applies.
  • aTotalEndpointCount - The total number of endpoints to which the campaign attempts to deliver messages.
  • aId - The unique activity ID.
  • aScheduledStart - The scheduled start time for the activity in ISO 8601 format.

aState :: Lens' ActivityResponse (Maybe Text) Source #

The state of the activity. Valid values: PENDING, INITIALIZING, RUNNING, PAUSED, CANCELLED, COMPLETED

aStart :: Lens' ActivityResponse (Maybe Text) Source #

The actual start time of the activity in ISO 8601 format.

aCampaignId :: Lens' ActivityResponse (Maybe Text) Source #

The ID of the campaign to which the activity applies.

aTimezonesCompletedCount :: Lens' ActivityResponse (Maybe Int) Source #

The total number of timezones completed.

aTimezonesTotalCount :: Lens' ActivityResponse (Maybe Int) Source #

The total number of unique timezones present in the segment.

aResult :: Lens' ActivityResponse (Maybe Text) Source #

Indicates whether the activity succeeded. Valid values: SUCCESS, FAIL

aTreatmentId :: Lens' ActivityResponse (Maybe Text) Source #

The ID of a variation of the campaign used for A/B testing.

aSuccessfulEndpointCount :: Lens' ActivityResponse (Maybe Int) Source #

The total number of endpoints to which the campaign successfully delivered messages.

aEnd :: Lens' ActivityResponse (Maybe Text) Source #

The actual time the activity was marked CANCELLED or COMPLETED. Provided in ISO 8601 format.

aApplicationId :: Lens' ActivityResponse (Maybe Text) Source #

The ID of the application to which the campaign applies.

aTotalEndpointCount :: Lens' ActivityResponse (Maybe Int) Source #

The total number of endpoints to which the campaign attempts to deliver messages.

aId :: Lens' ActivityResponse (Maybe Text) Source #

The unique activity ID.

aScheduledStart :: Lens' ActivityResponse (Maybe Text) Source #

The scheduled start time for the activity in ISO 8601 format.

AddressConfiguration

data AddressConfiguration Source #

Address configuration.

See: addressConfiguration smart constructor.

Instances

Eq AddressConfiguration Source # 
Data AddressConfiguration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddressConfiguration -> c AddressConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddressConfiguration #

toConstr :: AddressConfiguration -> Constr #

dataTypeOf :: AddressConfiguration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddressConfiguration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddressConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> AddressConfiguration -> AddressConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddressConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddressConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddressConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddressConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddressConfiguration -> m AddressConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddressConfiguration -> m AddressConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddressConfiguration -> m AddressConfiguration #

Read AddressConfiguration Source # 
Show AddressConfiguration Source # 
Generic AddressConfiguration Source # 
Hashable AddressConfiguration Source # 
ToJSON AddressConfiguration Source # 
NFData AddressConfiguration Source # 

Methods

rnf :: AddressConfiguration -> () #

type Rep AddressConfiguration Source # 
type Rep AddressConfiguration = D1 (MetaData "AddressConfiguration" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "AddressConfiguration'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_acSubstitutions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))) ((:*:) (S1 (MetaSel (Just Symbol "_acTitleOverride") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_acContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text)))))) ((:*:) (S1 (MetaSel (Just Symbol "_acRawContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_acBodyOverride") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_acChannelType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChannelType)))))))

addressConfiguration :: AddressConfiguration Source #

Creates a value of AddressConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • acSubstitutions - A map of substitution values for the message to be merged with the DefaultMessage's substitutions. Substitutions on this map take precedence over the all other substitutions.
  • acTitleOverride - Title override. If specified will override default title if applicable.
  • acContext - A map of custom attributes to attributes to be attached to the message for this address. This payload is added to the push notification's 'data.pinpoint' object or added to the email/sms delivery receipt event attributes.
  • acRawContent - The Raw JSON formatted string to be used as the payload. This value overrides the message.
  • acBodyOverride - Body override. If specified will override default body.
  • acChannelType - The channel type. Valid values: GCM | APNS | SMS | EMAIL

acSubstitutions :: Lens' AddressConfiguration (HashMap Text [Text]) Source #

A map of substitution values for the message to be merged with the DefaultMessage's substitutions. Substitutions on this map take precedence over the all other substitutions.

acTitleOverride :: Lens' AddressConfiguration (Maybe Text) Source #

Title override. If specified will override default title if applicable.

acContext :: Lens' AddressConfiguration (HashMap Text Text) Source #

A map of custom attributes to attributes to be attached to the message for this address. This payload is added to the push notification's 'data.pinpoint' object or added to the email/sms delivery receipt event attributes.

acRawContent :: Lens' AddressConfiguration (Maybe Text) Source #

The Raw JSON formatted string to be used as the payload. This value overrides the message.

acBodyOverride :: Lens' AddressConfiguration (Maybe Text) Source #

Body override. If specified will override default body.

acChannelType :: Lens' AddressConfiguration (Maybe ChannelType) Source #

The channel type. Valid values: GCM | APNS | SMS | EMAIL

ApplicationResponse

data ApplicationResponse Source #

Application Response.

See: applicationResponse smart constructor.

Instances

Eq ApplicationResponse Source # 
Data ApplicationResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationResponse -> c ApplicationResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationResponse #

toConstr :: ApplicationResponse -> Constr #

dataTypeOf :: ApplicationResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationResponse) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationResponse -> ApplicationResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationResponse -> m ApplicationResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationResponse -> m ApplicationResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationResponse -> m ApplicationResponse #

Read ApplicationResponse Source # 
Show ApplicationResponse Source # 
Generic ApplicationResponse Source # 
Hashable ApplicationResponse Source # 
FromJSON ApplicationResponse Source # 
NFData ApplicationResponse Source # 

Methods

rnf :: ApplicationResponse -> () #

type Rep ApplicationResponse Source # 
type Rep ApplicationResponse = D1 (MetaData "ApplicationResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "ApplicationResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_appName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_appId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

applicationResponse :: ApplicationResponse Source #

Creates a value of ApplicationResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • appName - The display name of the application.
  • appId - The unique application ID.

appName :: Lens' ApplicationResponse (Maybe Text) Source #

The display name of the application.

appId :: Lens' ApplicationResponse (Maybe Text) Source #

The unique application ID.

ApplicationSettingsResource

data ApplicationSettingsResource Source #

Application settings.

See: applicationSettingsResource smart constructor.

Instances

Eq ApplicationSettingsResource Source # 
Data ApplicationSettingsResource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationSettingsResource -> c ApplicationSettingsResource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationSettingsResource #

toConstr :: ApplicationSettingsResource -> Constr #

dataTypeOf :: ApplicationSettingsResource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationSettingsResource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationSettingsResource) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationSettingsResource -> ApplicationSettingsResource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationSettingsResource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationSettingsResource -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationSettingsResource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationSettingsResource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationSettingsResource -> m ApplicationSettingsResource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationSettingsResource -> m ApplicationSettingsResource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationSettingsResource -> m ApplicationSettingsResource #

Read ApplicationSettingsResource Source # 
Show ApplicationSettingsResource Source # 
Generic ApplicationSettingsResource Source # 
Hashable ApplicationSettingsResource Source # 
FromJSON ApplicationSettingsResource Source # 
NFData ApplicationSettingsResource Source # 
type Rep ApplicationSettingsResource Source # 
type Rep ApplicationSettingsResource = D1 (MetaData "ApplicationSettingsResource" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "ApplicationSettingsResource'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_asrLastModifiedDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_asrLimits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CampaignLimits)))) ((:*:) (S1 (MetaSel (Just Symbol "_asrQuietTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe QuietTime))) (S1 (MetaSel (Just Symbol "_asrApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

applicationSettingsResource :: ApplicationSettingsResource Source #

Creates a value of ApplicationSettingsResource with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • asrLastModifiedDate - The date that the settings were last updated in ISO 8601 format.
  • asrLimits - The default campaign limits for the app. These limits apply to each campaign for the app, unless the campaign overrides the default with limits of its own.
  • asrQuietTime - The default quiet time for the app. Each campaign for this app sends no messages during this time unless the campaign overrides the default with a quiet time of its own.
  • asrApplicationId - The unique ID for the application.

asrLastModifiedDate :: Lens' ApplicationSettingsResource (Maybe Text) Source #

The date that the settings were last updated in ISO 8601 format.

asrLimits :: Lens' ApplicationSettingsResource (Maybe CampaignLimits) Source #

The default campaign limits for the app. These limits apply to each campaign for the app, unless the campaign overrides the default with limits of its own.

asrQuietTime :: Lens' ApplicationSettingsResource (Maybe QuietTime) Source #

The default quiet time for the app. Each campaign for this app sends no messages during this time unless the campaign overrides the default with a quiet time of its own.

asrApplicationId :: Lens' ApplicationSettingsResource (Maybe Text) Source #

The unique ID for the application.

ApplicationsResponse

data ApplicationsResponse Source #

Get Applications Result.

See: applicationsResponse smart constructor.

Instances

Eq ApplicationsResponse Source # 
Data ApplicationsResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationsResponse -> c ApplicationsResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationsResponse #

toConstr :: ApplicationsResponse -> Constr #

dataTypeOf :: ApplicationsResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationsResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationsResponse) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationsResponse -> ApplicationsResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationsResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationsResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationsResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationsResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationsResponse -> m ApplicationsResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationsResponse -> m ApplicationsResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationsResponse -> m ApplicationsResponse #

Read ApplicationsResponse Source # 
Show ApplicationsResponse Source # 
Generic ApplicationsResponse Source # 
Hashable ApplicationsResponse Source # 
FromJSON ApplicationsResponse Source # 
NFData ApplicationsResponse Source # 

Methods

rnf :: ApplicationsResponse -> () #

type Rep ApplicationsResponse Source # 
type Rep ApplicationsResponse = D1 (MetaData "ApplicationsResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "ApplicationsResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_appNextToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_appItem") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ApplicationResponse])))))

applicationsResponse :: ApplicationsResponse Source #

Creates a value of ApplicationsResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • appNextToken - The string that you use in a subsequent request to get the next page of results in a paginated response.
  • appItem - List of applications returned in this page.

appNextToken :: Lens' ApplicationsResponse (Maybe Text) Source #

The string that you use in a subsequent request to get the next page of results in a paginated response.

appItem :: Lens' ApplicationsResponse [ApplicationResponse] Source #

List of applications returned in this page.

AttributeDimension

data AttributeDimension Source #

Custom attibute dimension

See: attributeDimension smart constructor.

Instances

Eq AttributeDimension Source # 
Data AttributeDimension Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AttributeDimension -> c AttributeDimension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AttributeDimension #

toConstr :: AttributeDimension -> Constr #

dataTypeOf :: AttributeDimension -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AttributeDimension) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AttributeDimension) #

gmapT :: (forall b. Data b => b -> b) -> AttributeDimension -> AttributeDimension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AttributeDimension -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AttributeDimension -> r #

gmapQ :: (forall d. Data d => d -> u) -> AttributeDimension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AttributeDimension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AttributeDimension -> m AttributeDimension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeDimension -> m AttributeDimension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeDimension -> m AttributeDimension #

Read AttributeDimension Source # 
Show AttributeDimension Source # 
Generic AttributeDimension Source # 
Hashable AttributeDimension Source # 
FromJSON AttributeDimension Source # 
ToJSON AttributeDimension Source # 
NFData AttributeDimension Source # 

Methods

rnf :: AttributeDimension -> () #

type Rep AttributeDimension Source # 
type Rep AttributeDimension = D1 (MetaData "AttributeDimension" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "AttributeDimension'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_adValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_adAttributeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AttributeType)))))

attributeDimension :: AttributeDimension Source #

Creates a value of AttributeDimension with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • adValues - The criteria values for the segment dimension. Endpoints with matching attribute values are included or excluded from the segment, depending on the setting for Type.
  • adAttributeType - The type of dimension: INCLUSIVE - Endpoints that match the criteria are included in the segment. EXCLUSIVE - Endpoints that match the criteria are excluded from the segment.

adValues :: Lens' AttributeDimension [Text] Source #

The criteria values for the segment dimension. Endpoints with matching attribute values are included or excluded from the segment, depending on the setting for Type.

adAttributeType :: Lens' AttributeDimension (Maybe AttributeType) Source #

The type of dimension: INCLUSIVE - Endpoints that match the criteria are included in the segment. EXCLUSIVE - Endpoints that match the criteria are excluded from the segment.

BaiduChannelRequest

data BaiduChannelRequest Source #

Baidu Cloud Push credentials

See: baiduChannelRequest smart constructor.

Instances

Eq BaiduChannelRequest Source # 
Data BaiduChannelRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BaiduChannelRequest -> c BaiduChannelRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BaiduChannelRequest #

toConstr :: BaiduChannelRequest -> Constr #

dataTypeOf :: BaiduChannelRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BaiduChannelRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BaiduChannelRequest) #

gmapT :: (forall b. Data b => b -> b) -> BaiduChannelRequest -> BaiduChannelRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BaiduChannelRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BaiduChannelRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> BaiduChannelRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BaiduChannelRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BaiduChannelRequest -> m BaiduChannelRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BaiduChannelRequest -> m BaiduChannelRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BaiduChannelRequest -> m BaiduChannelRequest #

Read BaiduChannelRequest Source # 
Show BaiduChannelRequest Source # 
Generic BaiduChannelRequest Source # 
Hashable BaiduChannelRequest Source # 
ToJSON BaiduChannelRequest Source # 
NFData BaiduChannelRequest Source # 

Methods

rnf :: BaiduChannelRequest -> () #

type Rep BaiduChannelRequest Source # 
type Rep BaiduChannelRequest = D1 (MetaData "BaiduChannelRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "BaiduChannelRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bcrAPIKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_bcrEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_bcrSecretKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

baiduChannelRequest :: BaiduChannelRequest Source #

Creates a value of BaiduChannelRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • bcrAPIKey - Platform credential API key from Baidu.
  • bcrEnabled - If the channel is enabled for sending messages.
  • bcrSecretKey - Platform credential Secret key from Baidu.

bcrAPIKey :: Lens' BaiduChannelRequest (Maybe Text) Source #

Platform credential API key from Baidu.

bcrEnabled :: Lens' BaiduChannelRequest (Maybe Bool) Source #

If the channel is enabled for sending messages.

bcrSecretKey :: Lens' BaiduChannelRequest (Maybe Text) Source #

Platform credential Secret key from Baidu.

BaiduChannelResponse

data BaiduChannelResponse Source #

Baidu Cloud Messaging channel definition

See: baiduChannelResponse smart constructor.

Instances

Eq BaiduChannelResponse Source # 
Data BaiduChannelResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BaiduChannelResponse -> c BaiduChannelResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BaiduChannelResponse #

toConstr :: BaiduChannelResponse -> Constr #

dataTypeOf :: BaiduChannelResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BaiduChannelResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BaiduChannelResponse) #

gmapT :: (forall b. Data b => b -> b) -> BaiduChannelResponse -> BaiduChannelResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BaiduChannelResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BaiduChannelResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> BaiduChannelResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BaiduChannelResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BaiduChannelResponse -> m BaiduChannelResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BaiduChannelResponse -> m BaiduChannelResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BaiduChannelResponse -> m BaiduChannelResponse #

Read BaiduChannelResponse Source # 
Show BaiduChannelResponse Source # 
Generic BaiduChannelResponse Source # 
Hashable BaiduChannelResponse Source # 
FromJSON BaiduChannelResponse Source # 
NFData BaiduChannelResponse Source # 

Methods

rnf :: BaiduChannelResponse -> () #

type Rep BaiduChannelResponse Source # 
type Rep BaiduChannelResponse = D1 (MetaData "BaiduChannelResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "BaiduChannelResponse'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bcPlatform") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bcLastModifiedDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_bcEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_bcCredential") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bcIsArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bcApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_bcVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_bcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_bcCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_bcLastModifiedBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bcHasCredential") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))))

baiduChannelResponse :: BaiduChannelResponse Source #

Creates a value of BaiduChannelResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bcPlatform :: Lens' BaiduChannelResponse (Maybe Text) Source #

The platform type. Will be BAIDU

bcEnabled :: Lens' BaiduChannelResponse (Maybe Bool) Source #

If the channel is enabled for sending messages.

bcCredential :: Lens' BaiduChannelResponse (Maybe Text) Source #

The Baidu API key from Baidu.

bcId :: Lens' BaiduChannelResponse (Maybe Text) Source #

Channel ID. Not used, only for backwards compatibility.

bcCreationDate :: Lens' BaiduChannelResponse (Maybe Text) Source #

When was this segment created

bcHasCredential :: Lens' BaiduChannelResponse (Maybe Bool) Source #

If the channel is registered with a credential for authentication.

BaiduMessage

data BaiduMessage Source #

Baidu Message.

See: baiduMessage smart constructor.

Instances

Eq BaiduMessage Source # 
Data BaiduMessage Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BaiduMessage -> c BaiduMessage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BaiduMessage #

toConstr :: BaiduMessage -> Constr #

dataTypeOf :: BaiduMessage -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BaiduMessage) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BaiduMessage) #

gmapT :: (forall b. Data b => b -> b) -> BaiduMessage -> BaiduMessage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BaiduMessage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BaiduMessage -> r #

gmapQ :: (forall d. Data d => d -> u) -> BaiduMessage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BaiduMessage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BaiduMessage -> m BaiduMessage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BaiduMessage -> m BaiduMessage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BaiduMessage -> m BaiduMessage #

Read BaiduMessage Source # 
Show BaiduMessage Source # 
Generic BaiduMessage Source # 

Associated Types

type Rep BaiduMessage :: * -> * #

Hashable BaiduMessage Source # 
ToJSON BaiduMessage Source # 
NFData BaiduMessage Source # 

Methods

rnf :: BaiduMessage -> () #

type Rep BaiduMessage Source # 
type Rep BaiduMessage = D1 (MetaData "BaiduMessage" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "BaiduMessage'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bmSubstitutions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))) ((:*:) (S1 (MetaSel (Just Symbol "_bmSilentPush") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_bmImageIconURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_bmRawContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_bmData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text)))) (S1 (MetaSel (Just Symbol "_bmSmallImageIconURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bmBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_bmURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bmSound") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bmAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Action))) (S1 (MetaSel (Just Symbol "_bmImageURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_bmTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bmIconReference") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

baiduMessage :: BaiduMessage Source #

Creates a value of BaiduMessage with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • bmSubstitutions - Default message substitutions. Can be overridden by individual address substitutions.
  • bmSilentPush - Indicates if the message should display on the users device. Silent pushes can be used for Remote Configuration and Phone Home use cases.
  • bmImageIconURL - The URL that points to an image used as the large icon to the notification content view.
  • bmRawContent - The Raw JSON formatted string to be used as the payload. This value overrides the message.
  • bmData - The data payload used for a silent push. This payload is added to the notifications' data.pinpoint.jsonBody' object
  • bmSmallImageIconURL - The URL that points to an image used as the small icon for the notification which will be used to represent the notification in the status bar and content view
  • bmBody - The message body of the notification, the email body or the text message.
  • bmURL - The URL to open in the user's mobile browser. Used if the value for Action is URL.
  • bmSound - Indicates a sound to play when the device receives the notification. Supports default, or the filename of a sound resource bundled in the app. Android sound files must reside in resraw/
  • bmAction - The action that occurs if the user taps a push notification delivered by the campaign: OPEN_APP - Your app launches, or it becomes the foreground app if it has been sent to the background. This is the default action. DEEP_LINK - Uses deep linking features in iOS and Android to open your app and display a designated user interface within the app. URL - The default mobile browser on the user's device launches and opens a web page at the URL you specify. Possible values include: OPEN_APP | DEEP_LINK | URL
  • bmImageURL - The URL that points to an image used in the push notification.
  • bmTitle - The message title that displays above the message on the user's device.
  • bmIconReference - The icon image name of the asset saved in your application.

bmSubstitutions :: Lens' BaiduMessage (HashMap Text [Text]) Source #

Default message substitutions. Can be overridden by individual address substitutions.

bmSilentPush :: Lens' BaiduMessage (Maybe Bool) Source #

Indicates if the message should display on the users device. Silent pushes can be used for Remote Configuration and Phone Home use cases.

bmImageIconURL :: Lens' BaiduMessage (Maybe Text) Source #

The URL that points to an image used as the large icon to the notification content view.

bmRawContent :: Lens' BaiduMessage (Maybe Text) Source #

The Raw JSON formatted string to be used as the payload. This value overrides the message.

bmData :: Lens' BaiduMessage (HashMap Text Text) Source #

The data payload used for a silent push. This payload is added to the notifications' data.pinpoint.jsonBody' object

bmSmallImageIconURL :: Lens' BaiduMessage (Maybe Text) Source #

The URL that points to an image used as the small icon for the notification which will be used to represent the notification in the status bar and content view

bmBody :: Lens' BaiduMessage (Maybe Text) Source #

The message body of the notification, the email body or the text message.

bmURL :: Lens' BaiduMessage (Maybe Text) Source #

The URL to open in the user's mobile browser. Used if the value for Action is URL.

bmSound :: Lens' BaiduMessage (Maybe Text) Source #

Indicates a sound to play when the device receives the notification. Supports default, or the filename of a sound resource bundled in the app. Android sound files must reside in resraw/

bmAction :: Lens' BaiduMessage (Maybe Action) Source #

The action that occurs if the user taps a push notification delivered by the campaign: OPEN_APP - Your app launches, or it becomes the foreground app if it has been sent to the background. This is the default action. DEEP_LINK - Uses deep linking features in iOS and Android to open your app and display a designated user interface within the app. URL - The default mobile browser on the user's device launches and opens a web page at the URL you specify. Possible values include: OPEN_APP | DEEP_LINK | URL

bmImageURL :: Lens' BaiduMessage (Maybe Text) Source #

The URL that points to an image used in the push notification.

bmTitle :: Lens' BaiduMessage (Maybe Text) Source #

The message title that displays above the message on the user's device.

bmIconReference :: Lens' BaiduMessage (Maybe Text) Source #

The icon image name of the asset saved in your application.

CampaignEmailMessage

data CampaignEmailMessage Source #

The email message configuration.

See: campaignEmailMessage smart constructor.

Instances

Eq CampaignEmailMessage Source # 
Data CampaignEmailMessage Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CampaignEmailMessage -> c CampaignEmailMessage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CampaignEmailMessage #

toConstr :: CampaignEmailMessage -> Constr #

dataTypeOf :: CampaignEmailMessage -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CampaignEmailMessage) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CampaignEmailMessage) #

gmapT :: (forall b. Data b => b -> b) -> CampaignEmailMessage -> CampaignEmailMessage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CampaignEmailMessage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CampaignEmailMessage -> r #

gmapQ :: (forall d. Data d => d -> u) -> CampaignEmailMessage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CampaignEmailMessage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CampaignEmailMessage -> m CampaignEmailMessage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignEmailMessage -> m CampaignEmailMessage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignEmailMessage -> m CampaignEmailMessage #

Read CampaignEmailMessage Source # 
Show CampaignEmailMessage Source # 
Generic CampaignEmailMessage Source # 
Hashable CampaignEmailMessage Source # 
FromJSON CampaignEmailMessage Source # 
ToJSON CampaignEmailMessage Source # 
NFData CampaignEmailMessage Source # 

Methods

rnf :: CampaignEmailMessage -> () #

type Rep CampaignEmailMessage Source # 
type Rep CampaignEmailMessage = D1 (MetaData "CampaignEmailMessage" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "CampaignEmailMessage'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cemBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cemFromAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cemHTMLBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cemTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

campaignEmailMessage :: CampaignEmailMessage Source #

Creates a value of CampaignEmailMessage with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cemBody - The email text body.
  • cemFromAddress - The email address used to send the email from. Defaults to use FromAddress specified in the Email Channel.
  • cemHTMLBody - The email html body.
  • cemTitle - The email title (Or subject).

cemFromAddress :: Lens' CampaignEmailMessage (Maybe Text) Source #

The email address used to send the email from. Defaults to use FromAddress specified in the Email Channel.

cemTitle :: Lens' CampaignEmailMessage (Maybe Text) Source #

The email title (Or subject).

CampaignLimits

data CampaignLimits Source #

Campaign Limits are used to limit the number of messages that can be sent to a user.

See: campaignLimits smart constructor.

Instances

Eq CampaignLimits Source # 
Data CampaignLimits Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CampaignLimits -> c CampaignLimits #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CampaignLimits #

toConstr :: CampaignLimits -> Constr #

dataTypeOf :: CampaignLimits -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CampaignLimits) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CampaignLimits) #

gmapT :: (forall b. Data b => b -> b) -> CampaignLimits -> CampaignLimits #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CampaignLimits -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CampaignLimits -> r #

gmapQ :: (forall d. Data d => d -> u) -> CampaignLimits -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CampaignLimits -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CampaignLimits -> m CampaignLimits #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignLimits -> m CampaignLimits #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignLimits -> m CampaignLimits #

Read CampaignLimits Source # 
Show CampaignLimits Source # 
Generic CampaignLimits Source # 

Associated Types

type Rep CampaignLimits :: * -> * #

Hashable CampaignLimits Source # 
FromJSON CampaignLimits Source # 
ToJSON CampaignLimits Source # 
NFData CampaignLimits Source # 

Methods

rnf :: CampaignLimits -> () #

type Rep CampaignLimits Source # 
type Rep CampaignLimits = D1 (MetaData "CampaignLimits" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "CampaignLimits'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_clMessagesPerSecond") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_clDaily") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))) ((:*:) (S1 (MetaSel (Just Symbol "_clTotal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_clMaximumDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))))

campaignLimits :: CampaignLimits Source #

Creates a value of CampaignLimits with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • clMessagesPerSecond - The maximum number of messages per second that the campaign will send. This is a best effort maximum cap and can go as high as 20000 and as low as 50
  • clDaily - The maximum number of messages that the campaign can send daily.
  • clTotal - The maximum total number of messages that the campaign can send.
  • clMaximumDuration - The maximum duration of a campaign from the scheduled start. Must be a minimum of 60 seconds.

clMessagesPerSecond :: Lens' CampaignLimits (Maybe Int) Source #

The maximum number of messages per second that the campaign will send. This is a best effort maximum cap and can go as high as 20000 and as low as 50

clDaily :: Lens' CampaignLimits (Maybe Int) Source #

The maximum number of messages that the campaign can send daily.

clTotal :: Lens' CampaignLimits (Maybe Int) Source #

The maximum total number of messages that the campaign can send.

clMaximumDuration :: Lens' CampaignLimits (Maybe Int) Source #

The maximum duration of a campaign from the scheduled start. Must be a minimum of 60 seconds.

CampaignResponse

data CampaignResponse Source #

Campaign definition

See: campaignResponse smart constructor.

Instances

Eq CampaignResponse Source # 
Data CampaignResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CampaignResponse -> c CampaignResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CampaignResponse #

toConstr :: CampaignResponse -> Constr #

dataTypeOf :: CampaignResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CampaignResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CampaignResponse) #

gmapT :: (forall b. Data b => b -> b) -> CampaignResponse -> CampaignResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CampaignResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CampaignResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> CampaignResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CampaignResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CampaignResponse -> m CampaignResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignResponse -> m CampaignResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignResponse -> m CampaignResponse #

Read CampaignResponse Source # 
Show CampaignResponse Source # 
Generic CampaignResponse Source # 
Hashable CampaignResponse Source # 
FromJSON CampaignResponse Source # 
NFData CampaignResponse Source # 

Methods

rnf :: CampaignResponse -> () #

type Rep CampaignResponse Source # 
type Rep CampaignResponse = D1 (MetaData "CampaignResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "CampaignResponse'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CampaignState))) (S1 (MetaSel (Just Symbol "_cLastModifiedDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cSchedule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Schedule))) (S1 (MetaSel (Just Symbol "_cTreatmentName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cLimits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CampaignLimits))) (S1 (MetaSel (Just Symbol "_cIsPaused") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_cDefaultState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CampaignState))) ((:*:) (S1 (MetaSel (Just Symbol "_cApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_cHoldoutPercent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))) ((:*:) (S1 (MetaSel (Just Symbol "_cTreatmentDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cMessageConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MessageConfiguration))) (S1 (MetaSel (Just Symbol "_cDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cSegmentId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cAdditionalTreatments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [TreatmentResource]))) (S1 (MetaSel (Just Symbol "_cSegmentVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))))))))

campaignResponse :: CampaignResponse Source #

Creates a value of CampaignResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cState - The campaign status. An A/B test campaign will have a status of COMPLETED only when all treatments have a status of COMPLETED.
  • cLastModifiedDate - The date the campaign was last updated in ISO 8601 format.
  • cSchedule - The campaign schedule.
  • cTreatmentName - The custom name of a variation of the campaign used for A/B testing.
  • cLimits - The campaign limits settings.
  • cIsPaused - Indicates whether the campaign is paused. A paused campaign does not send messages unless you resume it by setting IsPaused to false.
  • cDefaultState - The status of the campaign's default treatment. Only present for A/B test campaigns.
  • cApplicationId - The ID of the application to which the campaign applies.
  • cName - The custom name of the campaign.
  • cVersion - The campaign version number.
  • cHoldoutPercent - The allocated percentage of end users who will not receive messages from this campaign.
  • cTreatmentDescription - A custom description for the treatment.
  • cId - The unique campaign ID.
  • cCreationDate - The date the campaign was created in ISO 8601 format.
  • cMessageConfiguration - The message configuration settings.
  • cDescription - A description of the campaign.
  • cSegmentId - The ID of the segment to which the campaign sends messages.
  • cAdditionalTreatments - Treatments that are defined in addition to the default treatment.
  • cSegmentVersion - The version of the segment to which the campaign sends messages.

cState :: Lens' CampaignResponse (Maybe CampaignState) Source #

The campaign status. An A/B test campaign will have a status of COMPLETED only when all treatments have a status of COMPLETED.

cLastModifiedDate :: Lens' CampaignResponse (Maybe Text) Source #

The date the campaign was last updated in ISO 8601 format.

cTreatmentName :: Lens' CampaignResponse (Maybe Text) Source #

The custom name of a variation of the campaign used for A/B testing.

cLimits :: Lens' CampaignResponse (Maybe CampaignLimits) Source #

The campaign limits settings.

cIsPaused :: Lens' CampaignResponse (Maybe Bool) Source #

Indicates whether the campaign is paused. A paused campaign does not send messages unless you resume it by setting IsPaused to false.

cDefaultState :: Lens' CampaignResponse (Maybe CampaignState) Source #

The status of the campaign's default treatment. Only present for A/B test campaigns.

cApplicationId :: Lens' CampaignResponse (Maybe Text) Source #

The ID of the application to which the campaign applies.

cName :: Lens' CampaignResponse (Maybe Text) Source #

The custom name of the campaign.

cVersion :: Lens' CampaignResponse (Maybe Int) Source #

The campaign version number.

cHoldoutPercent :: Lens' CampaignResponse (Maybe Int) Source #

The allocated percentage of end users who will not receive messages from this campaign.

cTreatmentDescription :: Lens' CampaignResponse (Maybe Text) Source #

A custom description for the treatment.

cId :: Lens' CampaignResponse (Maybe Text) Source #

The unique campaign ID.

cCreationDate :: Lens' CampaignResponse (Maybe Text) Source #

The date the campaign was created in ISO 8601 format.

cDescription :: Lens' CampaignResponse (Maybe Text) Source #

A description of the campaign.

cSegmentId :: Lens' CampaignResponse (Maybe Text) Source #

The ID of the segment to which the campaign sends messages.

cAdditionalTreatments :: Lens' CampaignResponse [TreatmentResource] Source #

Treatments that are defined in addition to the default treatment.

cSegmentVersion :: Lens' CampaignResponse (Maybe Int) Source #

The version of the segment to which the campaign sends messages.

CampaignSmsMessage

data CampaignSmsMessage Source #

SMS message configuration.

See: campaignSmsMessage smart constructor.

Instances

Eq CampaignSmsMessage Source # 
Data CampaignSmsMessage Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CampaignSmsMessage -> c CampaignSmsMessage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CampaignSmsMessage #

toConstr :: CampaignSmsMessage -> Constr #

dataTypeOf :: CampaignSmsMessage -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CampaignSmsMessage) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CampaignSmsMessage) #

gmapT :: (forall b. Data b => b -> b) -> CampaignSmsMessage -> CampaignSmsMessage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CampaignSmsMessage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CampaignSmsMessage -> r #

gmapQ :: (forall d. Data d => d -> u) -> CampaignSmsMessage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CampaignSmsMessage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CampaignSmsMessage -> m CampaignSmsMessage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignSmsMessage -> m CampaignSmsMessage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignSmsMessage -> m CampaignSmsMessage #

Read CampaignSmsMessage Source # 
Show CampaignSmsMessage Source # 
Generic CampaignSmsMessage Source # 
Hashable CampaignSmsMessage Source # 
FromJSON CampaignSmsMessage Source # 
ToJSON CampaignSmsMessage Source # 
NFData CampaignSmsMessage Source # 

Methods

rnf :: CampaignSmsMessage -> () #

type Rep CampaignSmsMessage Source # 
type Rep CampaignSmsMessage = D1 (MetaData "CampaignSmsMessage" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "CampaignSmsMessage'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_csmBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_csmMessageType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MessageType))) (S1 (MetaSel (Just Symbol "_csmSenderId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

campaignSmsMessage :: CampaignSmsMessage Source #

Creates a value of CampaignSmsMessage with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

csmMessageType :: Lens' CampaignSmsMessage (Maybe MessageType) Source #

Is this is a transactional SMS message, otherwise a promotional message.

csmSenderId :: Lens' CampaignSmsMessage (Maybe Text) Source #

Sender ID of sent message.

CampaignState

data CampaignState Source #

State of the Campaign

See: campaignState smart constructor.

Instances

Eq CampaignState Source # 
Data CampaignState Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CampaignState -> c CampaignState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CampaignState #

toConstr :: CampaignState -> Constr #

dataTypeOf :: CampaignState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CampaignState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CampaignState) #

gmapT :: (forall b. Data b => b -> b) -> CampaignState -> CampaignState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CampaignState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CampaignState -> r #

gmapQ :: (forall d. Data d => d -> u) -> CampaignState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CampaignState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CampaignState -> m CampaignState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignState -> m CampaignState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignState -> m CampaignState #

Read CampaignState Source # 
Show CampaignState Source # 
Generic CampaignState Source # 

Associated Types

type Rep CampaignState :: * -> * #

Hashable CampaignState Source # 
FromJSON CampaignState Source # 
NFData CampaignState Source # 

Methods

rnf :: CampaignState -> () #

type Rep CampaignState Source # 
type Rep CampaignState = D1 (MetaData "CampaignState" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" True) (C1 (MetaCons "CampaignState'" PrefixI True) (S1 (MetaSel (Just Symbol "_csCampaignStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CampaignStatus))))

campaignState :: CampaignState Source #

Creates a value of CampaignState with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • csCampaignStatus - The status of the campaign, or the status of a treatment that belongs to an A/B test campaign. Valid values: SCHEDULED, EXECUTING, PENDING_NEXT_RUN, COMPLETED, PAUSED

csCampaignStatus :: Lens' CampaignState (Maybe CampaignStatus) Source #

The status of the campaign, or the status of a treatment that belongs to an A/B test campaign. Valid values: SCHEDULED, EXECUTING, PENDING_NEXT_RUN, COMPLETED, PAUSED

CampaignsResponse

data CampaignsResponse Source #

List of available campaigns.

See: campaignsResponse smart constructor.

Instances

Eq CampaignsResponse Source # 
Data CampaignsResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CampaignsResponse -> c CampaignsResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CampaignsResponse #

toConstr :: CampaignsResponse -> Constr #

dataTypeOf :: CampaignsResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CampaignsResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CampaignsResponse) #

gmapT :: (forall b. Data b => b -> b) -> CampaignsResponse -> CampaignsResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CampaignsResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CampaignsResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> CampaignsResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CampaignsResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CampaignsResponse -> m CampaignsResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignsResponse -> m CampaignsResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignsResponse -> m CampaignsResponse #

Read CampaignsResponse Source # 
Show CampaignsResponse Source # 
Generic CampaignsResponse Source # 
Hashable CampaignsResponse Source # 
FromJSON CampaignsResponse Source # 
NFData CampaignsResponse Source # 

Methods

rnf :: CampaignsResponse -> () #

type Rep CampaignsResponse Source # 
type Rep CampaignsResponse = D1 (MetaData "CampaignsResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "CampaignsResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cNextToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cItem") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CampaignResponse])))))

campaignsResponse :: CampaignsResponse Source #

Creates a value of CampaignsResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cNextToken - The string that you use in a subsequent request to get the next page of results in a paginated response.
  • cItem - A list of campaigns.

cNextToken :: Lens' CampaignsResponse (Maybe Text) Source #

The string that you use in a subsequent request to get the next page of results in a paginated response.

CreateApplicationRequest

data CreateApplicationRequest Source #

Application Request.

See: createApplicationRequest smart constructor.

Instances

Eq CreateApplicationRequest Source # 
Data CreateApplicationRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreateApplicationRequest -> c CreateApplicationRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreateApplicationRequest #

toConstr :: CreateApplicationRequest -> Constr #

dataTypeOf :: CreateApplicationRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreateApplicationRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreateApplicationRequest) #

gmapT :: (forall b. Data b => b -> b) -> CreateApplicationRequest -> CreateApplicationRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreateApplicationRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreateApplicationRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreateApplicationRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreateApplicationRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreateApplicationRequest -> m CreateApplicationRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreateApplicationRequest -> m CreateApplicationRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreateApplicationRequest -> m CreateApplicationRequest #

Read CreateApplicationRequest Source # 
Show CreateApplicationRequest Source # 
Generic CreateApplicationRequest Source # 
Hashable CreateApplicationRequest Source # 
ToJSON CreateApplicationRequest Source # 
NFData CreateApplicationRequest Source # 
type Rep CreateApplicationRequest Source # 
type Rep CreateApplicationRequest = D1 (MetaData "CreateApplicationRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" True) (C1 (MetaCons "CreateApplicationRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_carName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

createApplicationRequest :: CreateApplicationRequest Source #

Creates a value of CreateApplicationRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • carName - The display name of the application. Used in the Amazon Pinpoint console.

carName :: Lens' CreateApplicationRequest (Maybe Text) Source #

The display name of the application. Used in the Amazon Pinpoint console.

DefaultMessage

data DefaultMessage Source #

Default Message across push notification, email, and sms.

See: defaultMessage smart constructor.

Instances

Eq DefaultMessage Source # 
Data DefaultMessage Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefaultMessage -> c DefaultMessage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DefaultMessage #

toConstr :: DefaultMessage -> Constr #

dataTypeOf :: DefaultMessage -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DefaultMessage) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DefaultMessage) #

gmapT :: (forall b. Data b => b -> b) -> DefaultMessage -> DefaultMessage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultMessage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultMessage -> r #

gmapQ :: (forall d. Data d => d -> u) -> DefaultMessage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultMessage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultMessage -> m DefaultMessage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultMessage -> m DefaultMessage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultMessage -> m DefaultMessage #

Read DefaultMessage Source # 
Show DefaultMessage Source # 
Generic DefaultMessage Source # 

Associated Types

type Rep DefaultMessage :: * -> * #

Hashable DefaultMessage Source # 
ToJSON DefaultMessage Source # 
NFData DefaultMessage Source # 

Methods

rnf :: DefaultMessage -> () #

type Rep DefaultMessage Source # 
type Rep DefaultMessage = D1 (MetaData "DefaultMessage" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "DefaultMessage'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dmSubstitutions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))) (S1 (MetaSel (Just Symbol "_dmBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

defaultMessage :: DefaultMessage Source #

Creates a value of DefaultMessage with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • dmSubstitutions - Default message substitutions. Can be overridden by individual address substitutions.
  • dmBody - The message body of the notification, the email body or the text message.

dmSubstitutions :: Lens' DefaultMessage (HashMap Text [Text]) Source #

Default message substitutions. Can be overridden by individual address substitutions.

dmBody :: Lens' DefaultMessage (Maybe Text) Source #

The message body of the notification, the email body or the text message.

DefaultPushNotificationMessage

data DefaultPushNotificationMessage Source #

Default Push Notification Message.

See: defaultPushNotificationMessage smart constructor.

Instances

Eq DefaultPushNotificationMessage Source # 
Data DefaultPushNotificationMessage Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefaultPushNotificationMessage -> c DefaultPushNotificationMessage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DefaultPushNotificationMessage #

toConstr :: DefaultPushNotificationMessage -> Constr #

dataTypeOf :: DefaultPushNotificationMessage -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DefaultPushNotificationMessage) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DefaultPushNotificationMessage) #

gmapT :: (forall b. Data b => b -> b) -> DefaultPushNotificationMessage -> DefaultPushNotificationMessage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultPushNotificationMessage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultPushNotificationMessage -> r #

gmapQ :: (forall d. Data d => d -> u) -> DefaultPushNotificationMessage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultPushNotificationMessage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultPushNotificationMessage -> m DefaultPushNotificationMessage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultPushNotificationMessage -> m DefaultPushNotificationMessage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultPushNotificationMessage -> m DefaultPushNotificationMessage #

Read DefaultPushNotificationMessage Source # 
Show DefaultPushNotificationMessage Source # 
Generic DefaultPushNotificationMessage Source # 
Hashable DefaultPushNotificationMessage Source # 
ToJSON DefaultPushNotificationMessage Source # 
NFData DefaultPushNotificationMessage Source # 
type Rep DefaultPushNotificationMessage Source # 
type Rep DefaultPushNotificationMessage = D1 (MetaData "DefaultPushNotificationMessage" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "DefaultPushNotificationMessage'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dpnmSubstitutions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))) ((:*:) (S1 (MetaSel (Just Symbol "_dpnmSilentPush") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_dpnmData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dpnmBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dpnmURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_dpnmAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Action))) (S1 (MetaSel (Just Symbol "_dpnmTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

defaultPushNotificationMessage :: DefaultPushNotificationMessage Source #

Creates a value of DefaultPushNotificationMessage with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • dpnmSubstitutions - Default message substitutions. Can be overridden by individual address substitutions.
  • dpnmSilentPush - Indicates if the message should display on the users device. Silent pushes can be used for Remote Configuration and Phone Home use cases.
  • dpnmData - The data payload used for a silent push. This payload is added to the notifications' data.pinpoint.jsonBody' object
  • dpnmBody - The message body of the notification, the email body or the text message.
  • dpnmURL - The URL to open in the user's mobile browser. Used if the value for Action is URL.
  • dpnmAction - The action that occurs if the user taps a push notification delivered by the campaign: OPEN_APP - Your app launches, or it becomes the foreground app if it has been sent to the background. This is the default action. DEEP_LINK - Uses deep linking features in iOS and Android to open your app and display a designated user interface within the app. URL - The default mobile browser on the user's device launches and opens a web page at the URL you specify. Possible values include: OPEN_APP | DEEP_LINK | URL
  • dpnmTitle - The message title that displays above the message on the user's device.

dpnmSubstitutions :: Lens' DefaultPushNotificationMessage (HashMap Text [Text]) Source #

Default message substitutions. Can be overridden by individual address substitutions.

dpnmSilentPush :: Lens' DefaultPushNotificationMessage (Maybe Bool) Source #

Indicates if the message should display on the users device. Silent pushes can be used for Remote Configuration and Phone Home use cases.

dpnmData :: Lens' DefaultPushNotificationMessage (HashMap Text Text) Source #

The data payload used for a silent push. This payload is added to the notifications' data.pinpoint.jsonBody' object

dpnmBody :: Lens' DefaultPushNotificationMessage (Maybe Text) Source #

The message body of the notification, the email body or the text message.

dpnmURL :: Lens' DefaultPushNotificationMessage (Maybe Text) Source #

The URL to open in the user's mobile browser. Used if the value for Action is URL.

dpnmAction :: Lens' DefaultPushNotificationMessage (Maybe Action) Source #

The action that occurs if the user taps a push notification delivered by the campaign: OPEN_APP - Your app launches, or it becomes the foreground app if it has been sent to the background. This is the default action. DEEP_LINK - Uses deep linking features in iOS and Android to open your app and display a designated user interface within the app. URL - The default mobile browser on the user's device launches and opens a web page at the URL you specify. Possible values include: OPEN_APP | DEEP_LINK | URL

dpnmTitle :: Lens' DefaultPushNotificationMessage (Maybe Text) Source #

The message title that displays above the message on the user's device.

DirectMessageConfiguration

data DirectMessageConfiguration Source #

The message configuration.

See: directMessageConfiguration smart constructor.

Instances

Eq DirectMessageConfiguration Source # 
Data DirectMessageConfiguration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectMessageConfiguration -> c DirectMessageConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectMessageConfiguration #

toConstr :: DirectMessageConfiguration -> Constr #

dataTypeOf :: DirectMessageConfiguration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectMessageConfiguration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectMessageConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> DirectMessageConfiguration -> DirectMessageConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectMessageConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectMessageConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectMessageConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectMessageConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectMessageConfiguration -> m DirectMessageConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectMessageConfiguration -> m DirectMessageConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectMessageConfiguration -> m DirectMessageConfiguration #

Read DirectMessageConfiguration Source # 
Show DirectMessageConfiguration Source # 
Generic DirectMessageConfiguration Source # 
Hashable DirectMessageConfiguration Source # 
ToJSON DirectMessageConfiguration Source # 
NFData DirectMessageConfiguration Source # 
type Rep DirectMessageConfiguration Source # 
type Rep DirectMessageConfiguration = D1 (MetaData "DirectMessageConfiguration" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "DirectMessageConfiguration'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dmcAPNSMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe APNSMessage))) ((:*:) (S1 (MetaSel (Just Symbol "_dmcGCMMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GCMMessage))) (S1 (MetaSel (Just Symbol "_dmcDefaultMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DefaultMessage))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dmcADMMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ADMMessage))) (S1 (MetaSel (Just Symbol "_dmcSMSMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SMSMessage)))) ((:*:) (S1 (MetaSel (Just Symbol "_dmcBaiduMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BaiduMessage))) (S1 (MetaSel (Just Symbol "_dmcDefaultPushNotificationMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DefaultPushNotificationMessage)))))))

directMessageConfiguration :: DirectMessageConfiguration Source #

Creates a value of DirectMessageConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • dmcAPNSMessage - The message to APNS channels. Overrides the default push notification message.
  • dmcGCMMessage - The message to GCM channels. Overrides the default push notification message.
  • dmcDefaultMessage - The default message for all channels.
  • dmcADMMessage - The message to ADM channels. Overrides the default push notification message.
  • dmcSMSMessage - The message to SMS channels. Overrides the default message.
  • dmcBaiduMessage - The message to Baidu GCM channels. Overrides the default push notification message.
  • dmcDefaultPushNotificationMessage - The default push notification message for all push channels.

dmcAPNSMessage :: Lens' DirectMessageConfiguration (Maybe APNSMessage) Source #

The message to APNS channels. Overrides the default push notification message.

dmcGCMMessage :: Lens' DirectMessageConfiguration (Maybe GCMMessage) Source #

The message to GCM channels. Overrides the default push notification message.

dmcADMMessage :: Lens' DirectMessageConfiguration (Maybe ADMMessage) Source #

The message to ADM channels. Overrides the default push notification message.

dmcSMSMessage :: Lens' DirectMessageConfiguration (Maybe SMSMessage) Source #

The message to SMS channels. Overrides the default message.

dmcBaiduMessage :: Lens' DirectMessageConfiguration (Maybe BaiduMessage) Source #

The message to Baidu GCM channels. Overrides the default push notification message.

dmcDefaultPushNotificationMessage :: Lens' DirectMessageConfiguration (Maybe DefaultPushNotificationMessage) Source #

The default push notification message for all push channels.

EmailChannelRequest

data EmailChannelRequest Source #

Email Channel Request

See: emailChannelRequest smart constructor.

Instances

Eq EmailChannelRequest Source # 
Data EmailChannelRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EmailChannelRequest -> c EmailChannelRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EmailChannelRequest #

toConstr :: EmailChannelRequest -> Constr #

dataTypeOf :: EmailChannelRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EmailChannelRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EmailChannelRequest) #

gmapT :: (forall b. Data b => b -> b) -> EmailChannelRequest -> EmailChannelRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EmailChannelRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EmailChannelRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> EmailChannelRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EmailChannelRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EmailChannelRequest -> m EmailChannelRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EmailChannelRequest -> m EmailChannelRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EmailChannelRequest -> m EmailChannelRequest #

Read EmailChannelRequest Source # 
Show EmailChannelRequest Source # 
Generic EmailChannelRequest Source # 
Hashable EmailChannelRequest Source # 
ToJSON EmailChannelRequest Source # 
NFData EmailChannelRequest Source # 

Methods

rnf :: EmailChannelRequest -> () #

type Rep EmailChannelRequest Source # 
type Rep EmailChannelRequest = D1 (MetaData "EmailChannelRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "EmailChannelRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ecrEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_ecrFromAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ecrIdentity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ecrRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

emailChannelRequest :: EmailChannelRequest Source #

Creates a value of EmailChannelRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ecrEnabled - If the channel is enabled for sending messages.
  • ecrFromAddress - The email address used to send emails from.
  • ecrIdentity - The ARN of an identity verified with SES.
  • ecrRoleARN - The ARN of an IAM Role used to submit events to Mobile Analytics' event ingestion service

ecrEnabled :: Lens' EmailChannelRequest (Maybe Bool) Source #

If the channel is enabled for sending messages.

ecrFromAddress :: Lens' EmailChannelRequest (Maybe Text) Source #

The email address used to send emails from.

ecrIdentity :: Lens' EmailChannelRequest (Maybe Text) Source #

The ARN of an identity verified with SES.

ecrRoleARN :: Lens' EmailChannelRequest (Maybe Text) Source #

The ARN of an IAM Role used to submit events to Mobile Analytics' event ingestion service

EmailChannelResponse

data EmailChannelResponse Source #

Email Channel Response.

See: emailChannelResponse smart constructor.

Instances

Eq EmailChannelResponse Source # 
Data EmailChannelResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EmailChannelResponse -> c EmailChannelResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EmailChannelResponse #

toConstr :: EmailChannelResponse -> Constr #

dataTypeOf :: EmailChannelResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EmailChannelResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EmailChannelResponse) #

gmapT :: (forall b. Data b => b -> b) -> EmailChannelResponse -> EmailChannelResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EmailChannelResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EmailChannelResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> EmailChannelResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EmailChannelResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EmailChannelResponse -> m EmailChannelResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EmailChannelResponse -> m EmailChannelResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EmailChannelResponse -> m EmailChannelResponse #

Read EmailChannelResponse Source # 
Show EmailChannelResponse Source # 
Generic EmailChannelResponse Source # 
Hashable EmailChannelResponse Source # 
FromJSON EmailChannelResponse Source # 
NFData EmailChannelResponse Source # 

Methods

rnf :: EmailChannelResponse -> () #

type Rep EmailChannelResponse Source # 
type Rep EmailChannelResponse = D1 (MetaData "EmailChannelResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "EmailChannelResponse'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ecPlatform") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ecLastModifiedDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ecEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "_ecFromAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ecIsArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_ecApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ecVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) ((:*:) (S1 (MetaSel (Just Symbol "_ecId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ecCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ecLastModifiedBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ecIdentity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ecHasCredential") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_ecRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

emailChannelResponse :: EmailChannelResponse Source #

Creates a value of EmailChannelResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ecEnabled :: Lens' EmailChannelResponse (Maybe Bool) Source #

If the channel is enabled for sending messages.

ecFromAddress :: Lens' EmailChannelResponse (Maybe Text) Source #

The email address used to send emails from.

ecApplicationId :: Lens' EmailChannelResponse (Maybe Text) Source #

The unique ID of the application to which the email channel belongs.

ecId :: Lens' EmailChannelResponse (Maybe Text) Source #

Channel ID. Not used, only for backwards compatibility.

ecCreationDate :: Lens' EmailChannelResponse (Maybe Text) Source #

The date that the settings were last updated in ISO 8601 format.

ecLastModifiedBy :: Lens' EmailChannelResponse (Maybe Text) Source #

Who last updated this entry

ecIdentity :: Lens' EmailChannelResponse (Maybe Text) Source #

The ARN of an identity verified with SES.

ecHasCredential :: Lens' EmailChannelResponse (Maybe Bool) Source #

If the channel is registered with a credential for authentication.

ecRoleARN :: Lens' EmailChannelResponse (Maybe Text) Source #

The ARN of an IAM Role used to submit events to Mobile Analytics' event ingestion service

EndpointBatchItem

data EndpointBatchItem Source #

Endpoint update request

See: endpointBatchItem smart constructor.

Instances

Eq EndpointBatchItem Source # 
Data EndpointBatchItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndpointBatchItem -> c EndpointBatchItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EndpointBatchItem #

toConstr :: EndpointBatchItem -> Constr #

dataTypeOf :: EndpointBatchItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EndpointBatchItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EndpointBatchItem) #

gmapT :: (forall b. Data b => b -> b) -> EndpointBatchItem -> EndpointBatchItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndpointBatchItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndpointBatchItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> EndpointBatchItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EndpointBatchItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndpointBatchItem -> m EndpointBatchItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointBatchItem -> m EndpointBatchItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointBatchItem -> m EndpointBatchItem #

Read EndpointBatchItem Source # 
Show EndpointBatchItem Source # 
Generic EndpointBatchItem Source # 
Hashable EndpointBatchItem Source # 
ToJSON EndpointBatchItem Source # 
NFData EndpointBatchItem Source # 

Methods

rnf :: EndpointBatchItem -> () #

type Rep EndpointBatchItem Source # 
type Rep EndpointBatchItem = D1 (MetaData "EndpointBatchItem" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "EndpointBatchItem'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ebiRequestId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ebiMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Double)))) (S1 (MetaSel (Just Symbol "_ebiLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EndpointLocation))))) ((:*:) (S1 (MetaSel (Just Symbol "_ebiDemographic") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EndpointDemographic))) ((:*:) (S1 (MetaSel (Just Symbol "_ebiAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ebiEffectiveDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ebiUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EndpointUser))) ((:*:) (S1 (MetaSel (Just Symbol "_ebiAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))) (S1 (MetaSel (Just Symbol "_ebiEndpointStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_ebiOptOut") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ebiId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ebiChannelType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChannelType))))))))

endpointBatchItem :: EndpointBatchItem Source #

Creates a value of EndpointBatchItem with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ebiRequestId - The unique ID for the most recent request to update the endpoint.
  • ebiMetrics - Custom metrics that your app reports to Amazon Pinpoint.
  • ebiLocation - The endpoint location attributes.
  • ebiDemographic - The endpoint demographic attributes.
  • ebiAddress - The address or token of the endpoint as provided by your push provider (e.g. DeviceToken or RegistrationId).
  • ebiEffectiveDate - The last time the endpoint was updated. Provided in ISO 8601 format.
  • ebiUser - Custom user-specific attributes that your app reports to Amazon Pinpoint.
  • ebiAttributes - Custom attributes that your app reports to Amazon Pinpoint. You can use these attributes as selection criteria when you create a segment.
  • ebiEndpointStatus - The endpoint status. Can be either ACTIVE or INACTIVE. Will be set to INACTIVE if a delivery fails. Will be set to ACTIVE if the address is updated.
  • ebiOptOut - Indicates whether a user has opted out of receiving messages with one of the following values: ALL - User has opted out of all messages. NONE - Users has not opted out and receives all messages.
  • ebiId - The unique Id for the Endpoint in the batch.
  • ebiChannelType - The channel type. Valid values: GCM | APNS | SMS | EMAIL

ebiRequestId :: Lens' EndpointBatchItem (Maybe Text) Source #

The unique ID for the most recent request to update the endpoint.

ebiMetrics :: Lens' EndpointBatchItem (HashMap Text Double) Source #

Custom metrics that your app reports to Amazon Pinpoint.

ebiLocation :: Lens' EndpointBatchItem (Maybe EndpointLocation) Source #

The endpoint location attributes.

ebiDemographic :: Lens' EndpointBatchItem (Maybe EndpointDemographic) Source #

The endpoint demographic attributes.

ebiAddress :: Lens' EndpointBatchItem (Maybe Text) Source #

The address or token of the endpoint as provided by your push provider (e.g. DeviceToken or RegistrationId).

ebiEffectiveDate :: Lens' EndpointBatchItem (Maybe Text) Source #

The last time the endpoint was updated. Provided in ISO 8601 format.

ebiUser :: Lens' EndpointBatchItem (Maybe EndpointUser) Source #

Custom user-specific attributes that your app reports to Amazon Pinpoint.

ebiAttributes :: Lens' EndpointBatchItem (HashMap Text [Text]) Source #

Custom attributes that your app reports to Amazon Pinpoint. You can use these attributes as selection criteria when you create a segment.

ebiEndpointStatus :: Lens' EndpointBatchItem (Maybe Text) Source #

The endpoint status. Can be either ACTIVE or INACTIVE. Will be set to INACTIVE if a delivery fails. Will be set to ACTIVE if the address is updated.

ebiOptOut :: Lens' EndpointBatchItem (Maybe Text) Source #

Indicates whether a user has opted out of receiving messages with one of the following values: ALL - User has opted out of all messages. NONE - Users has not opted out and receives all messages.

ebiId :: Lens' EndpointBatchItem (Maybe Text) Source #

The unique Id for the Endpoint in the batch.

ebiChannelType :: Lens' EndpointBatchItem (Maybe ChannelType) Source #

The channel type. Valid values: GCM | APNS | SMS | EMAIL

EndpointBatchRequest

data EndpointBatchRequest Source #

Endpoint batch update request.

See: endpointBatchRequest smart constructor.

Instances

Eq EndpointBatchRequest Source # 
Data EndpointBatchRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndpointBatchRequest -> c EndpointBatchRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EndpointBatchRequest #

toConstr :: EndpointBatchRequest -> Constr #

dataTypeOf :: EndpointBatchRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EndpointBatchRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EndpointBatchRequest) #

gmapT :: (forall b. Data b => b -> b) -> EndpointBatchRequest -> EndpointBatchRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndpointBatchRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndpointBatchRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> EndpointBatchRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EndpointBatchRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndpointBatchRequest -> m EndpointBatchRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointBatchRequest -> m EndpointBatchRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointBatchRequest -> m EndpointBatchRequest #

Read EndpointBatchRequest Source # 
Show EndpointBatchRequest Source # 
Generic EndpointBatchRequest Source # 
Hashable EndpointBatchRequest Source # 
ToJSON EndpointBatchRequest Source # 
NFData EndpointBatchRequest Source # 

Methods

rnf :: EndpointBatchRequest -> () #

type Rep EndpointBatchRequest Source # 
type Rep EndpointBatchRequest = D1 (MetaData "EndpointBatchRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" True) (C1 (MetaCons "EndpointBatchRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_ebrItem") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [EndpointBatchItem]))))

endpointBatchRequest :: EndpointBatchRequest Source #

Creates a value of EndpointBatchRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ebrItem - List of items to update. Maximum 100 items

ebrItem :: Lens' EndpointBatchRequest [EndpointBatchItem] Source #

List of items to update. Maximum 100 items

EndpointDemographic

data EndpointDemographic Source #

Endpoint demographic data

See: endpointDemographic smart constructor.

Instances

Eq EndpointDemographic Source # 
Data EndpointDemographic Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndpointDemographic -> c EndpointDemographic #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EndpointDemographic #

toConstr :: EndpointDemographic -> Constr #

dataTypeOf :: EndpointDemographic -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EndpointDemographic) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EndpointDemographic) #

gmapT :: (forall b. Data b => b -> b) -> EndpointDemographic -> EndpointDemographic #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndpointDemographic -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndpointDemographic -> r #

gmapQ :: (forall d. Data d => d -> u) -> EndpointDemographic -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EndpointDemographic -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndpointDemographic -> m EndpointDemographic #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointDemographic -> m EndpointDemographic #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointDemographic -> m EndpointDemographic #

Read EndpointDemographic Source # 
Show EndpointDemographic Source # 
Generic EndpointDemographic Source # 
Hashable EndpointDemographic Source # 
FromJSON EndpointDemographic Source # 
ToJSON EndpointDemographic Source # 
NFData EndpointDemographic Source # 

Methods

rnf :: EndpointDemographic -> () #

type Rep EndpointDemographic Source # 

endpointDemographic :: EndpointDemographic Source #

Creates a value of EndpointDemographic with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • edPlatform - The endpoint platform, such as ios or android.
  • edPlatformVersion - The endpoint platform version.
  • edLocale - The endpoint locale in the following format: The ISO 639-1 alpha-2 code, followed by an underscore, followed by an ISO 3166-1 alpha-2 value.
  • edAppVersion - The version of the application associated with the endpoint.
  • edModel - The endpoint model, such as iPhone.
  • edMake - The endpoint make, such as such as Apple or Samsung.
  • edModelVersion - The endpoint model version.
  • edTimezone - The timezone of the endpoint. Specified as a tz database value, such as Americas/Los_Angeles.

edPlatform :: Lens' EndpointDemographic (Maybe Text) Source #

The endpoint platform, such as ios or android.

edPlatformVersion :: Lens' EndpointDemographic (Maybe Text) Source #

The endpoint platform version.

edLocale :: Lens' EndpointDemographic (Maybe Text) Source #

The endpoint locale in the following format: The ISO 639-1 alpha-2 code, followed by an underscore, followed by an ISO 3166-1 alpha-2 value.

edAppVersion :: Lens' EndpointDemographic (Maybe Text) Source #

The version of the application associated with the endpoint.

edModel :: Lens' EndpointDemographic (Maybe Text) Source #

The endpoint model, such as iPhone.

edMake :: Lens' EndpointDemographic (Maybe Text) Source #

The endpoint make, such as such as Apple or Samsung.

edModelVersion :: Lens' EndpointDemographic (Maybe Text) Source #

The endpoint model version.

edTimezone :: Lens' EndpointDemographic (Maybe Text) Source #

The timezone of the endpoint. Specified as a tz database value, such as Americas/Los_Angeles.

EndpointLocation

data EndpointLocation Source #

Endpoint location data

See: endpointLocation smart constructor.

Instances

Eq EndpointLocation Source # 
Data EndpointLocation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndpointLocation -> c EndpointLocation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EndpointLocation #

toConstr :: EndpointLocation -> Constr #

dataTypeOf :: EndpointLocation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EndpointLocation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EndpointLocation) #

gmapT :: (forall b. Data b => b -> b) -> EndpointLocation -> EndpointLocation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndpointLocation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndpointLocation -> r #

gmapQ :: (forall d. Data d => d -> u) -> EndpointLocation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EndpointLocation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndpointLocation -> m EndpointLocation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointLocation -> m EndpointLocation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointLocation -> m EndpointLocation #

Read EndpointLocation Source # 
Show EndpointLocation Source # 
Generic EndpointLocation Source # 
Hashable EndpointLocation Source # 
FromJSON EndpointLocation Source # 
ToJSON EndpointLocation Source # 
NFData EndpointLocation Source # 

Methods

rnf :: EndpointLocation -> () #

type Rep EndpointLocation Source # 

endpointLocation :: EndpointLocation Source #

Creates a value of EndpointLocation with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • elPostalCode - The postal code or zip code of the endpoint.
  • elLatitude - The latitude of the endpoint location. Rounded to one decimal (Roughly corresponding to a mile).
  • elCountry - Country according to ISO 3166-1 Alpha-2 codes. For example, US.
  • elCity - The city where the endpoint is located.
  • elRegion - The region of the endpoint location. For example, corresponds to a state in US.
  • elLongitude - The longitude of the endpoint location. Rounded to one decimal (Roughly corresponding to a mile).

elPostalCode :: Lens' EndpointLocation (Maybe Text) Source #

The postal code or zip code of the endpoint.

elLatitude :: Lens' EndpointLocation (Maybe Double) Source #

The latitude of the endpoint location. Rounded to one decimal (Roughly corresponding to a mile).

elCountry :: Lens' EndpointLocation (Maybe Text) Source #

Country according to ISO 3166-1 Alpha-2 codes. For example, US.

elCity :: Lens' EndpointLocation (Maybe Text) Source #

The city where the endpoint is located.

elRegion :: Lens' EndpointLocation (Maybe Text) Source #

The region of the endpoint location. For example, corresponds to a state in US.

elLongitude :: Lens' EndpointLocation (Maybe Double) Source #

The longitude of the endpoint location. Rounded to one decimal (Roughly corresponding to a mile).

EndpointMessageResult

data EndpointMessageResult Source #

The result from sending a message to an endpoint.

See: endpointMessageResult smart constructor.

Instances

Eq EndpointMessageResult Source # 
Data EndpointMessageResult Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndpointMessageResult -> c EndpointMessageResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EndpointMessageResult #

toConstr :: EndpointMessageResult -> Constr #

dataTypeOf :: EndpointMessageResult -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EndpointMessageResult) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EndpointMessageResult) #

gmapT :: (forall b. Data b => b -> b) -> EndpointMessageResult -> EndpointMessageResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndpointMessageResult -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndpointMessageResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> EndpointMessageResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EndpointMessageResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndpointMessageResult -> m EndpointMessageResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointMessageResult -> m EndpointMessageResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointMessageResult -> m EndpointMessageResult #

Read EndpointMessageResult Source # 
Show EndpointMessageResult Source # 
Generic EndpointMessageResult Source # 
Hashable EndpointMessageResult Source # 
FromJSON EndpointMessageResult Source # 
NFData EndpointMessageResult Source # 

Methods

rnf :: EndpointMessageResult -> () #

type Rep EndpointMessageResult Source # 
type Rep EndpointMessageResult = D1 (MetaData "EndpointMessageResult" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "EndpointMessageResult'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_emrDeliveryStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeliveryStatus))) (S1 (MetaSel (Just Symbol "_emrAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_emrStatusMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_emrUpdatedToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_emrStatusCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))))))

endpointMessageResult :: EndpointMessageResult Source #

Creates a value of EndpointMessageResult with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

emrAddress :: Lens' EndpointMessageResult (Maybe Text) Source #

Address that endpoint message was delivered to.

emrStatusMessage :: Lens' EndpointMessageResult (Maybe Text) Source #

Status message for message delivery.

emrUpdatedToken :: Lens' EndpointMessageResult (Maybe Text) Source #

If token was updated as part of delivery. (This is GCM Specific)

emrStatusCode :: Lens' EndpointMessageResult (Maybe Int) Source #

Downstream service status code.

EndpointRequest

data EndpointRequest Source #

Endpoint update request

See: endpointRequest smart constructor.

Instances

Eq EndpointRequest Source # 
Data EndpointRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndpointRequest -> c EndpointRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EndpointRequest #

toConstr :: EndpointRequest -> Constr #

dataTypeOf :: EndpointRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EndpointRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EndpointRequest) #

gmapT :: (forall b. Data b => b -> b) -> EndpointRequest -> EndpointRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndpointRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndpointRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> EndpointRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EndpointRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndpointRequest -> m EndpointRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointRequest -> m EndpointRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointRequest -> m EndpointRequest #

Read EndpointRequest Source # 
Show EndpointRequest Source # 
Generic EndpointRequest Source # 
Hashable EndpointRequest Source # 
ToJSON EndpointRequest Source # 
NFData EndpointRequest Source # 

Methods

rnf :: EndpointRequest -> () #

type Rep EndpointRequest Source # 
type Rep EndpointRequest = D1 (MetaData "EndpointRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "EndpointRequest'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_erRequestId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_erMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Double))))) ((:*:) (S1 (MetaSel (Just Symbol "_erLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EndpointLocation))) ((:*:) (S1 (MetaSel (Just Symbol "_erDemographic") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EndpointDemographic))) (S1 (MetaSel (Just Symbol "_erAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_erEffectiveDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_erUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EndpointUser))) (S1 (MetaSel (Just Symbol "_erAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))))) ((:*:) (S1 (MetaSel (Just Symbol "_erEndpointStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_erOptOut") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_erChannelType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChannelType))))))))

endpointRequest :: EndpointRequest Source #

Creates a value of EndpointRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • erRequestId - The unique ID for the most recent request to update the endpoint.
  • erMetrics - Custom metrics that your app reports to Amazon Pinpoint.
  • erLocation - The endpoint location attributes.
  • erDemographic - The endpoint demographic attributes.
  • erAddress - The address or token of the endpoint as provided by your push provider (e.g. DeviceToken or RegistrationId).
  • erEffectiveDate - The last time the endpoint was updated. Provided in ISO 8601 format.
  • erUser - Custom user-specific attributes that your app reports to Amazon Pinpoint.
  • erAttributes - Custom attributes that your app reports to Amazon Pinpoint. You can use these attributes as selection criteria when you create a segment.
  • erEndpointStatus - The endpoint status. Can be either ACTIVE or INACTIVE. Will be set to INACTIVE if a delivery fails. Will be set to ACTIVE if the address is updated.
  • erOptOut - Indicates whether a user has opted out of receiving messages with one of the following values: ALL - User has opted out of all messages. NONE - Users has not opted out and receives all messages.
  • erChannelType - The channel type. Valid values: GCM | APNS | SMS | EMAIL

erRequestId :: Lens' EndpointRequest (Maybe Text) Source #

The unique ID for the most recent request to update the endpoint.

erMetrics :: Lens' EndpointRequest (HashMap Text Double) Source #

Custom metrics that your app reports to Amazon Pinpoint.

erLocation :: Lens' EndpointRequest (Maybe EndpointLocation) Source #

The endpoint location attributes.

erDemographic :: Lens' EndpointRequest (Maybe EndpointDemographic) Source #

The endpoint demographic attributes.

erAddress :: Lens' EndpointRequest (Maybe Text) Source #

The address or token of the endpoint as provided by your push provider (e.g. DeviceToken or RegistrationId).

erEffectiveDate :: Lens' EndpointRequest (Maybe Text) Source #

The last time the endpoint was updated. Provided in ISO 8601 format.

erUser :: Lens' EndpointRequest (Maybe EndpointUser) Source #

Custom user-specific attributes that your app reports to Amazon Pinpoint.

erAttributes :: Lens' EndpointRequest (HashMap Text [Text]) Source #

Custom attributes that your app reports to Amazon Pinpoint. You can use these attributes as selection criteria when you create a segment.

erEndpointStatus :: Lens' EndpointRequest (Maybe Text) Source #

The endpoint status. Can be either ACTIVE or INACTIVE. Will be set to INACTIVE if a delivery fails. Will be set to ACTIVE if the address is updated.

erOptOut :: Lens' EndpointRequest (Maybe Text) Source #

Indicates whether a user has opted out of receiving messages with one of the following values: ALL - User has opted out of all messages. NONE - Users has not opted out and receives all messages.

erChannelType :: Lens' EndpointRequest (Maybe ChannelType) Source #

The channel type. Valid values: GCM | APNS | SMS | EMAIL

EndpointResponse

data EndpointResponse Source #

Endpoint response

See: endpointResponse smart constructor.

Instances

Eq EndpointResponse Source # 
Data EndpointResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndpointResponse -> c EndpointResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EndpointResponse #

toConstr :: EndpointResponse -> Constr #

dataTypeOf :: EndpointResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EndpointResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EndpointResponse) #

gmapT :: (forall b. Data b => b -> b) -> EndpointResponse -> EndpointResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndpointResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndpointResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> EndpointResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EndpointResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndpointResponse -> m EndpointResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointResponse -> m EndpointResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointResponse -> m EndpointResponse #

Read EndpointResponse Source # 
Show EndpointResponse Source # 
Generic EndpointResponse Source # 
Hashable EndpointResponse Source # 
FromJSON EndpointResponse Source # 
NFData EndpointResponse Source # 

Methods

rnf :: EndpointResponse -> () #

type Rep EndpointResponse Source # 
type Rep EndpointResponse = D1 (MetaData "EndpointResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "EndpointResponse'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_eRequestId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_eMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Double)))) (S1 (MetaSel (Just Symbol "_eLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EndpointLocation))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_eDemographic") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EndpointDemographic))) (S1 (MetaSel (Just Symbol "_eCohortId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_eAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_eEffectiveDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_eUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EndpointUser))) (S1 (MetaSel (Just Symbol "_eApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_eAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))) (S1 (MetaSel (Just Symbol "_eEndpointStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_eOptOut") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_eId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_eCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_eChannelType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChannelType))))))))

endpointResponse :: EndpointResponse Source #

Creates a value of EndpointResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • eRequestId - The unique ID for the most recent request to update the endpoint.
  • eMetrics - Custom metrics that your app reports to Amazon Pinpoint.
  • eLocation - The endpoint location attributes.
  • eDemographic - The endpoint demographic attributes.
  • eCohortId - A number from 0 - 99 that represents the cohort the endpoint is assigned to. Endpoints are grouped into cohorts randomly, and each cohort contains approximately 1 percent of the endpoints for an app. Amazon Pinpoint assigns cohorts to the holdout or treatment allocations for a campaign.
  • eAddress - The address or token of the endpoint as provided by your push provider (e.g. DeviceToken or RegistrationId).
  • eEffectiveDate - The last time the endpoint was updated. Provided in ISO 8601 format.
  • eUser - Custom user-specific attributes that your app reports to Amazon Pinpoint.
  • eApplicationId - The ID of the application associated with the endpoint.
  • eAttributes - Custom attributes that your app reports to Amazon Pinpoint. You can use these attributes as selection criteria when you create a segment.
  • eEndpointStatus - The endpoint status. Can be either ACTIVE or INACTIVE. Will be set to INACTIVE if a delivery fails. Will be set to ACTIVE if the address is updated.
  • eOptOut - Indicates whether a user has opted out of receiving messages with one of the following values: ALL - User has opted out of all messages. NONE - Users has not opted out and receives all messages.
  • eId - The unique ID that you assigned to the endpoint. The ID should be a globally unique identifier (GUID) to ensure that it is unique compared to all other endpoints for the application.
  • eCreationDate - The last time the endpoint was created. Provided in ISO 8601 format.
  • eChannelType - The channel type. Valid values: GCM | APNS | SMS | EMAIL

eRequestId :: Lens' EndpointResponse (Maybe Text) Source #

The unique ID for the most recent request to update the endpoint.

eMetrics :: Lens' EndpointResponse (HashMap Text Double) Source #

Custom metrics that your app reports to Amazon Pinpoint.

eLocation :: Lens' EndpointResponse (Maybe EndpointLocation) Source #

The endpoint location attributes.

eDemographic :: Lens' EndpointResponse (Maybe EndpointDemographic) Source #

The endpoint demographic attributes.

eCohortId :: Lens' EndpointResponse (Maybe Text) Source #

A number from 0 - 99 that represents the cohort the endpoint is assigned to. Endpoints are grouped into cohorts randomly, and each cohort contains approximately 1 percent of the endpoints for an app. Amazon Pinpoint assigns cohorts to the holdout or treatment allocations for a campaign.

eAddress :: Lens' EndpointResponse (Maybe Text) Source #

The address or token of the endpoint as provided by your push provider (e.g. DeviceToken or RegistrationId).

eEffectiveDate :: Lens' EndpointResponse (Maybe Text) Source #

The last time the endpoint was updated. Provided in ISO 8601 format.

eUser :: Lens' EndpointResponse (Maybe EndpointUser) Source #

Custom user-specific attributes that your app reports to Amazon Pinpoint.

eApplicationId :: Lens' EndpointResponse (Maybe Text) Source #

The ID of the application associated with the endpoint.

eAttributes :: Lens' EndpointResponse (HashMap Text [Text]) Source #

Custom attributes that your app reports to Amazon Pinpoint. You can use these attributes as selection criteria when you create a segment.

eEndpointStatus :: Lens' EndpointResponse (Maybe Text) Source #

The endpoint status. Can be either ACTIVE or INACTIVE. Will be set to INACTIVE if a delivery fails. Will be set to ACTIVE if the address is updated.

eOptOut :: Lens' EndpointResponse (Maybe Text) Source #

Indicates whether a user has opted out of receiving messages with one of the following values: ALL - User has opted out of all messages. NONE - Users has not opted out and receives all messages.

eId :: Lens' EndpointResponse (Maybe Text) Source #

The unique ID that you assigned to the endpoint. The ID should be a globally unique identifier (GUID) to ensure that it is unique compared to all other endpoints for the application.

eCreationDate :: Lens' EndpointResponse (Maybe Text) Source #

The last time the endpoint was created. Provided in ISO 8601 format.

eChannelType :: Lens' EndpointResponse (Maybe ChannelType) Source #

The channel type. Valid values: GCM | APNS | SMS | EMAIL

EndpointSendConfiguration

data EndpointSendConfiguration Source #

Endpoint send configuration.

See: endpointSendConfiguration smart constructor.

Instances

Eq EndpointSendConfiguration Source # 
Data EndpointSendConfiguration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndpointSendConfiguration -> c EndpointSendConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EndpointSendConfiguration #

toConstr :: EndpointSendConfiguration -> Constr #

dataTypeOf :: EndpointSendConfiguration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EndpointSendConfiguration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EndpointSendConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> EndpointSendConfiguration -> EndpointSendConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndpointSendConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndpointSendConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> EndpointSendConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EndpointSendConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndpointSendConfiguration -> m EndpointSendConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointSendConfiguration -> m EndpointSendConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointSendConfiguration -> m EndpointSendConfiguration #

Read EndpointSendConfiguration Source # 
Show EndpointSendConfiguration Source # 
Generic EndpointSendConfiguration Source # 
Hashable EndpointSendConfiguration Source # 
ToJSON EndpointSendConfiguration Source # 
NFData EndpointSendConfiguration Source # 
type Rep EndpointSendConfiguration Source # 
type Rep EndpointSendConfiguration = D1 (MetaData "EndpointSendConfiguration" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "EndpointSendConfiguration'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_escSubstitutions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))) (S1 (MetaSel (Just Symbol "_escTitleOverride") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_escContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_escRawContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_escBodyOverride") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

endpointSendConfiguration :: EndpointSendConfiguration Source #

Creates a value of EndpointSendConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • escSubstitutions - A map of substitution values for the message to be merged with the DefaultMessage's substitutions. Substitutions on this map take precedence over the all other substitutions.
  • escTitleOverride - Title override. If specified will override default title if applicable.
  • escContext - A map of custom attributes to attributes to be attached to the message for this address. This payload is added to the push notification's 'data.pinpoint' object or added to the email/sms delivery receipt event attributes.
  • escRawContent - The Raw JSON formatted string to be used as the payload. This value overrides the message.
  • escBodyOverride - Body override. If specified will override default body.

escSubstitutions :: Lens' EndpointSendConfiguration (HashMap Text [Text]) Source #

A map of substitution values for the message to be merged with the DefaultMessage's substitutions. Substitutions on this map take precedence over the all other substitutions.

escTitleOverride :: Lens' EndpointSendConfiguration (Maybe Text) Source #

Title override. If specified will override default title if applicable.

escContext :: Lens' EndpointSendConfiguration (HashMap Text Text) Source #

A map of custom attributes to attributes to be attached to the message for this address. This payload is added to the push notification's 'data.pinpoint' object or added to the email/sms delivery receipt event attributes.

escRawContent :: Lens' EndpointSendConfiguration (Maybe Text) Source #

The Raw JSON formatted string to be used as the payload. This value overrides the message.

escBodyOverride :: Lens' EndpointSendConfiguration (Maybe Text) Source #

Body override. If specified will override default body.

EndpointUser

data EndpointUser Source #

Endpoint user specific custom userAttributes

See: endpointUser smart constructor.

Instances

Eq EndpointUser Source # 
Data EndpointUser Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndpointUser -> c EndpointUser #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EndpointUser #

toConstr :: EndpointUser -> Constr #

dataTypeOf :: EndpointUser -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EndpointUser) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EndpointUser) #

gmapT :: (forall b. Data b => b -> b) -> EndpointUser -> EndpointUser #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndpointUser -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndpointUser -> r #

gmapQ :: (forall d. Data d => d -> u) -> EndpointUser -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EndpointUser -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndpointUser -> m EndpointUser #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointUser -> m EndpointUser #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndpointUser -> m EndpointUser #

Read EndpointUser Source # 
Show EndpointUser Source # 
Generic EndpointUser Source # 

Associated Types

type Rep EndpointUser :: * -> * #

Hashable EndpointUser Source # 
FromJSON EndpointUser Source # 
ToJSON EndpointUser Source # 
NFData EndpointUser Source # 

Methods

rnf :: EndpointUser -> () #

type Rep EndpointUser Source # 
type Rep EndpointUser = D1 (MetaData "EndpointUser" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "EndpointUser'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_euUserAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))) (S1 (MetaSel (Just Symbol "_euUserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

endpointUser :: EndpointUser Source #

Creates a value of EndpointUser with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

euUserAttributes :: Lens' EndpointUser (HashMap Text [Text]) Source #

Custom attributes specific to the user.

euUserId :: Lens' EndpointUser (Maybe Text) Source #

The unique ID of the user.

EventStream

data EventStream Source #

Model for an event publishing subscription export.

See: eventStream smart constructor.

Instances

Eq EventStream Source # 
Data EventStream Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventStream -> c EventStream #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventStream #

toConstr :: EventStream -> Constr #

dataTypeOf :: EventStream -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EventStream) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventStream) #

gmapT :: (forall b. Data b => b -> b) -> EventStream -> EventStream #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventStream -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventStream -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventStream -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventStream -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventStream -> m EventStream #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventStream -> m EventStream #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventStream -> m EventStream #

Read EventStream Source # 
Show EventStream Source # 
Generic EventStream Source # 

Associated Types

type Rep EventStream :: * -> * #

Hashable EventStream Source # 
FromJSON EventStream Source # 
NFData EventStream Source # 

Methods

rnf :: EventStream -> () #

type Rep EventStream Source # 
type Rep EventStream = D1 (MetaData "EventStream" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "EventStream'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_esLastUpdatedBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_esLastModifiedDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_esDestinationStreamARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_esApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_esExternalId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_esRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

eventStream :: EventStream Source #

Creates a value of EventStream with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • esLastUpdatedBy - The IAM user who last modified the event stream.
  • esLastModifiedDate - The date the event stream was last updated in ISO 8601 format.
  • esDestinationStreamARN - The Amazon Resource Name (ARN) of the Amazon Kinesis stream or Firehose delivery stream to which you want to publish events. Firehose ARN: arn:aws:firehose:REGION:ACCOUNT_ID:deliverystreamSTREAM_NAME Kinesis ARN: arn:aws:kinesis:REGION:ACCOUNT_ID:streamSTREAM_NAME
  • esApplicationId - The ID of the application from which events should be published.
  • esExternalId - The external ID assigned the IAM role that authorizes Amazon Pinpoint to publish to the stream.
  • esRoleARN - The IAM role that authorizes Amazon Pinpoint to publish events to the stream in your account.

esLastUpdatedBy :: Lens' EventStream (Maybe Text) Source #

The IAM user who last modified the event stream.

esLastModifiedDate :: Lens' EventStream (Maybe Text) Source #

The date the event stream was last updated in ISO 8601 format.

esDestinationStreamARN :: Lens' EventStream (Maybe Text) Source #

The Amazon Resource Name (ARN) of the Amazon Kinesis stream or Firehose delivery stream to which you want to publish events. Firehose ARN: arn:aws:firehose:REGION:ACCOUNT_ID:deliverystreamSTREAM_NAME Kinesis ARN: arn:aws:kinesis:REGION:ACCOUNT_ID:streamSTREAM_NAME

esApplicationId :: Lens' EventStream (Maybe Text) Source #

The ID of the application from which events should be published.

esExternalId :: Lens' EventStream (Maybe Text) Source #

The external ID assigned the IAM role that authorizes Amazon Pinpoint to publish to the stream.

esRoleARN :: Lens' EventStream (Maybe Text) Source #

The IAM role that authorizes Amazon Pinpoint to publish events to the stream in your account.

GCMChannelRequest

data GCMChannelRequest Source #

Google Cloud Messaging credentials

See: gcmChannelRequest smart constructor.

Instances

Eq GCMChannelRequest Source # 
Data GCMChannelRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GCMChannelRequest -> c GCMChannelRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GCMChannelRequest #

toConstr :: GCMChannelRequest -> Constr #

dataTypeOf :: GCMChannelRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GCMChannelRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GCMChannelRequest) #

gmapT :: (forall b. Data b => b -> b) -> GCMChannelRequest -> GCMChannelRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GCMChannelRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GCMChannelRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> GCMChannelRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GCMChannelRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GCMChannelRequest -> m GCMChannelRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GCMChannelRequest -> m GCMChannelRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GCMChannelRequest -> m GCMChannelRequest #

Read GCMChannelRequest Source # 
Show GCMChannelRequest Source # 
Generic GCMChannelRequest Source # 
Hashable GCMChannelRequest Source # 
ToJSON GCMChannelRequest Source # 
NFData GCMChannelRequest Source # 

Methods

rnf :: GCMChannelRequest -> () #

type Rep GCMChannelRequest Source # 
type Rep GCMChannelRequest = D1 (MetaData "GCMChannelRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "GCMChannelRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gcrAPIKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gcrEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))

gcmChannelRequest :: GCMChannelRequest Source #

Creates a value of GCMChannelRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • gcrAPIKey - Platform credential API key from Google.
  • gcrEnabled - If the channel is enabled for sending messages.

gcrAPIKey :: Lens' GCMChannelRequest (Maybe Text) Source #

Platform credential API key from Google.

gcrEnabled :: Lens' GCMChannelRequest (Maybe Bool) Source #

If the channel is enabled for sending messages.

GCMChannelResponse

data GCMChannelResponse Source #

Google Cloud Messaging channel definition

See: gcmChannelResponse smart constructor.

Instances

Eq GCMChannelResponse Source # 
Data GCMChannelResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GCMChannelResponse -> c GCMChannelResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GCMChannelResponse #

toConstr :: GCMChannelResponse -> Constr #

dataTypeOf :: GCMChannelResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GCMChannelResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GCMChannelResponse) #

gmapT :: (forall b. Data b => b -> b) -> GCMChannelResponse -> GCMChannelResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GCMChannelResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GCMChannelResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> GCMChannelResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GCMChannelResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GCMChannelResponse -> m GCMChannelResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GCMChannelResponse -> m GCMChannelResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GCMChannelResponse -> m GCMChannelResponse #

Read GCMChannelResponse Source # 
Show GCMChannelResponse Source # 
Generic GCMChannelResponse Source # 
Hashable GCMChannelResponse Source # 
FromJSON GCMChannelResponse Source # 
NFData GCMChannelResponse Source # 

Methods

rnf :: GCMChannelResponse -> () #

type Rep GCMChannelResponse Source # 
type Rep GCMChannelResponse = D1 (MetaData "GCMChannelResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "GCMChannelResponse'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gcPlatform") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gcLastModifiedDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_gcEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_gcCredential") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gcIsArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gcApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_gcVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_gcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_gcCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_gcLastModifiedBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gcHasCredential") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))))

gcmChannelResponse :: GCMChannelResponse Source #

Creates a value of GCMChannelResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gcPlatform :: Lens' GCMChannelResponse (Maybe Text) Source #

The platform type. Will be GCM

gcEnabled :: Lens' GCMChannelResponse (Maybe Bool) Source #

If the channel is enabled for sending messages.

gcCredential :: Lens' GCMChannelResponse (Maybe Text) Source #

The GCM API key from Google.

gcIsArchived :: Lens' GCMChannelResponse (Maybe Bool) Source #

Is this channel archived

gcApplicationId :: Lens' GCMChannelResponse (Maybe Text) Source #

The ID of the application to which the channel applies.

gcId :: Lens' GCMChannelResponse (Maybe Text) Source #

Channel ID. Not used. Present only for backwards compatibility.

gcCreationDate :: Lens' GCMChannelResponse (Maybe Text) Source #

When was this segment created

gcLastModifiedBy :: Lens' GCMChannelResponse (Maybe Text) Source #

Who last updated this entry

gcHasCredential :: Lens' GCMChannelResponse (Maybe Bool) Source #

If the channel is registered with a credential for authentication.

GCMMessage

data GCMMessage Source #

GCM Message.

See: gcmMessage smart constructor.

Instances

Eq GCMMessage Source # 
Data GCMMessage Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GCMMessage -> c GCMMessage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GCMMessage #

toConstr :: GCMMessage -> Constr #

dataTypeOf :: GCMMessage -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GCMMessage) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GCMMessage) #

gmapT :: (forall b. Data b => b -> b) -> GCMMessage -> GCMMessage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GCMMessage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GCMMessage -> r #

gmapQ :: (forall d. Data d => d -> u) -> GCMMessage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GCMMessage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GCMMessage -> m GCMMessage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GCMMessage -> m GCMMessage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GCMMessage -> m GCMMessage #

Read GCMMessage Source # 
Show GCMMessage Source # 
Generic GCMMessage Source # 

Associated Types

type Rep GCMMessage :: * -> * #

Hashable GCMMessage Source # 
ToJSON GCMMessage Source # 
NFData GCMMessage Source # 

Methods

rnf :: GCMMessage -> () #

type Rep GCMMessage Source # 
type Rep GCMMessage = D1 (MetaData "GCMMessage" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "GCMMessage'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gmSubstitutions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))) (S1 (MetaSel (Just Symbol "_gmSilentPush") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_gmImageIconURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gmPriority") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gmRawContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gmData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_gmRestrictedPackageName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gmSmallImageIconURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gmBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gmTimeToLive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))) ((:*:) (S1 (MetaSel (Just Symbol "_gmURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gmSound") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gmAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Action))) (S1 (MetaSel (Just Symbol "_gmCollapseKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_gmImageURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_gmTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_gmIconReference") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))))

gcmMessage :: GCMMessage Source #

Creates a value of GCMMessage with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • gmSubstitutions - Default message substitutions. Can be overridden by individual address substitutions.
  • gmSilentPush - Indicates if the message should display on the users device. Silent pushes can be used for Remote Configuration and Phone Home use cases.
  • gmImageIconURL - The URL that points to an image used as the large icon to the notification content view.
  • gmPriority - Is this a transaction priority message or lower priority.
  • gmRawContent - The Raw JSON formatted string to be used as the payload. This value overrides the message.
  • gmData - The data payload used for a silent push. This payload is added to the notifications' data.pinpoint.jsonBody' object
  • gmRestrictedPackageName - This parameter specifies the package name of the application where the registration tokens must match in order to receive the message.
  • gmSmallImageIconURL - The URL that points to an image used as the small icon for the notification which will be used to represent the notification in the status bar and content view
  • gmBody - The message body of the notification, the email body or the text message.
  • gmTimeToLive - This parameter specifies how long (in seconds) the message should be kept in GCM storage if the device is offline. The maximum time to live supported is 4 weeks, and the default value is 4 weeks.
  • gmURL - The URL to open in the user's mobile browser. Used if the value for Action is URL.
  • gmSound - Indicates a sound to play when the device receives the notification. Supports default, or the filename of a sound resource bundled in the app. Android sound files must reside in resraw/
  • gmAction - The action that occurs if the user taps a push notification delivered by the campaign: OPEN_APP - Your app launches, or it becomes the foreground app if it has been sent to the background. This is the default action. DEEP_LINK - Uses deep linking features in iOS and Android to open your app and display a designated user interface within the app. URL - The default mobile browser on the user's device launches and opens a web page at the URL you specify. Possible values include: OPEN_APP | DEEP_LINK | URL
  • gmCollapseKey - This parameter identifies a group of messages (e.g., with collapse_key: "Updates Available") that can be collapsed, so that only the last message gets sent when delivery can be resumed. This is intended to avoid sending too many of the same messages when the device comes back online or becomes active.
  • gmImageURL - The URL that points to an image used in the push notification.
  • gmTitle - The message title that displays above the message on the user's device.
  • gmIconReference - The icon image name of the asset saved in your application.

gmSubstitutions :: Lens' GCMMessage (HashMap Text [Text]) Source #

Default message substitutions. Can be overridden by individual address substitutions.

gmSilentPush :: Lens' GCMMessage (Maybe Bool) Source #

Indicates if the message should display on the users device. Silent pushes can be used for Remote Configuration and Phone Home use cases.

gmImageIconURL :: Lens' GCMMessage (Maybe Text) Source #

The URL that points to an image used as the large icon to the notification content view.

gmPriority :: Lens' GCMMessage (Maybe Text) Source #

Is this a transaction priority message or lower priority.

gmRawContent :: Lens' GCMMessage (Maybe Text) Source #

The Raw JSON formatted string to be used as the payload. This value overrides the message.

gmData :: Lens' GCMMessage (HashMap Text Text) Source #

The data payload used for a silent push. This payload is added to the notifications' data.pinpoint.jsonBody' object

gmRestrictedPackageName :: Lens' GCMMessage (Maybe Text) Source #

This parameter specifies the package name of the application where the registration tokens must match in order to receive the message.

gmSmallImageIconURL :: Lens' GCMMessage (Maybe Text) Source #

The URL that points to an image used as the small icon for the notification which will be used to represent the notification in the status bar and content view

gmBody :: Lens' GCMMessage (Maybe Text) Source #

The message body of the notification, the email body or the text message.

gmTimeToLive :: Lens' GCMMessage (Maybe Int) Source #

This parameter specifies how long (in seconds) the message should be kept in GCM storage if the device is offline. The maximum time to live supported is 4 weeks, and the default value is 4 weeks.

gmURL :: Lens' GCMMessage (Maybe Text) Source #

The URL to open in the user's mobile browser. Used if the value for Action is URL.

gmSound :: Lens' GCMMessage (Maybe Text) Source #

Indicates a sound to play when the device receives the notification. Supports default, or the filename of a sound resource bundled in the app. Android sound files must reside in resraw/

gmAction :: Lens' GCMMessage (Maybe Action) Source #

The action that occurs if the user taps a push notification delivered by the campaign: OPEN_APP - Your app launches, or it becomes the foreground app if it has been sent to the background. This is the default action. DEEP_LINK - Uses deep linking features in iOS and Android to open your app and display a designated user interface within the app. URL - The default mobile browser on the user's device launches and opens a web page at the URL you specify. Possible values include: OPEN_APP | DEEP_LINK | URL

gmCollapseKey :: Lens' GCMMessage (Maybe Text) Source #

This parameter identifies a group of messages (e.g., with collapse_key: "Updates Available") that can be collapsed, so that only the last message gets sent when delivery can be resumed. This is intended to avoid sending too many of the same messages when the device comes back online or becomes active.

gmImageURL :: Lens' GCMMessage (Maybe Text) Source #

The URL that points to an image used in the push notification.

gmTitle :: Lens' GCMMessage (Maybe Text) Source #

The message title that displays above the message on the user's device.

gmIconReference :: Lens' GCMMessage (Maybe Text) Source #

The icon image name of the asset saved in your application.

ImportJobRequest

data ImportJobRequest Source #

See: importJobRequest smart constructor.

Instances

Eq ImportJobRequest Source # 
Data ImportJobRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportJobRequest -> c ImportJobRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportJobRequest #

toConstr :: ImportJobRequest -> Constr #

dataTypeOf :: ImportJobRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImportJobRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportJobRequest) #

gmapT :: (forall b. Data b => b -> b) -> ImportJobRequest -> ImportJobRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportJobRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportJobRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImportJobRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportJobRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportJobRequest -> m ImportJobRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportJobRequest -> m ImportJobRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportJobRequest -> m ImportJobRequest #

Read ImportJobRequest Source # 
Show ImportJobRequest Source # 
Generic ImportJobRequest Source # 
Hashable ImportJobRequest Source # 
ToJSON ImportJobRequest Source # 
NFData ImportJobRequest Source # 

Methods

rnf :: ImportJobRequest -> () #

type Rep ImportJobRequest Source # 

importJobRequest :: ImportJobRequest Source #

Creates a value of ImportJobRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • iSegmentName - A custom name for the segment created by the import job. Use if DefineSegment is true.
  • iFormat - The format of the files that contain the endpoint definitions. Valid values: CSV, JSON
  • iDefineSegment - Sets whether the endpoints create a segment when they are imported.
  • iRegisterEndpoints - Sets whether the endpoints are registered with Amazon Pinpoint when they are imported.
  • iExternalId - A unique, custom ID assigned to the IAM role that restricts who can assume the role.
  • iS3URL - A URL that points to the location within an Amazon S3 bucket that contains the endpoints to import. The location can be a folder or a single file. The URL should follow this format: s3:/bucket-namefolder-name/file-name Amazon Pinpoint will import endpoints from this location and any subfolders it contains.
  • iSegmentId - The ID of the segment to update if the import job is meant to update an existing segment.
  • iRoleARN - The Amazon Resource Name (ARN) of an IAM role that grants Amazon Pinpoint access to the Amazon S3 location that contains the endpoints to import.

iSegmentName :: Lens' ImportJobRequest (Maybe Text) Source #

A custom name for the segment created by the import job. Use if DefineSegment is true.

iFormat :: Lens' ImportJobRequest (Maybe DefinitionFormat) Source #

The format of the files that contain the endpoint definitions. Valid values: CSV, JSON

iDefineSegment :: Lens' ImportJobRequest (Maybe Bool) Source #

Sets whether the endpoints create a segment when they are imported.

iRegisterEndpoints :: Lens' ImportJobRequest (Maybe Bool) Source #

Sets whether the endpoints are registered with Amazon Pinpoint when they are imported.

iExternalId :: Lens' ImportJobRequest (Maybe Text) Source #

A unique, custom ID assigned to the IAM role that restricts who can assume the role.

iS3URL :: Lens' ImportJobRequest (Maybe Text) Source #

A URL that points to the location within an Amazon S3 bucket that contains the endpoints to import. The location can be a folder or a single file. The URL should follow this format: s3:/bucket-namefolder-name/file-name Amazon Pinpoint will import endpoints from this location and any subfolders it contains.

iSegmentId :: Lens' ImportJobRequest (Maybe Text) Source #

The ID of the segment to update if the import job is meant to update an existing segment.

iRoleARN :: Lens' ImportJobRequest (Maybe Text) Source #

The Amazon Resource Name (ARN) of an IAM role that grants Amazon Pinpoint access to the Amazon S3 location that contains the endpoints to import.

ImportJobResource

data ImportJobResource Source #

See: importJobResource smart constructor.

Instances

Eq ImportJobResource Source # 
Data ImportJobResource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportJobResource -> c ImportJobResource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportJobResource #

toConstr :: ImportJobResource -> Constr #

dataTypeOf :: ImportJobResource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImportJobResource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportJobResource) #

gmapT :: (forall b. Data b => b -> b) -> ImportJobResource -> ImportJobResource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportJobResource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportJobResource -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImportJobResource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportJobResource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportJobResource -> m ImportJobResource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportJobResource -> m ImportJobResource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportJobResource -> m ImportJobResource #

Read ImportJobResource Source # 
Show ImportJobResource Source # 
Generic ImportJobResource Source # 
Hashable ImportJobResource Source # 
FromJSON ImportJobResource Source # 
NFData ImportJobResource Source # 

Methods

rnf :: ImportJobResource -> () #

type Rep ImportJobResource Source # 

importJobResource :: ImportJobResource Source #

Creates a value of ImportJobResource with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ijrSegmentName - A custom name for the segment created by the import job. Use if DefineSegment is true.
  • ijrFormat - The format of the files that contain the endpoint definitions. Valid values: CSV, JSON
  • ijrDefineSegment - Sets whether the endpoints create a segment when they are imported.
  • ijrRegisterEndpoints - Sets whether the endpoints are registered with Amazon Pinpoint when they are imported.
  • ijrExternalId - A unique, custom ID assigned to the IAM role that restricts who can assume the role.
  • ijrS3URL - A URL that points to the location within an Amazon S3 bucket that contains the endpoints to import. The location can be a folder or a single file. The URL should follow this format: s3:/bucket-namefolder-name/file-name Amazon Pinpoint will import endpoints from this location and any subfolders it contains.
  • ijrSegmentId - The ID of the segment to update if the import job is meant to update an existing segment.
  • ijrRoleARN - The Amazon Resource Name (ARN) of an IAM role that grants Amazon Pinpoint access to the Amazon S3 location that contains the endpoints to import.

ijrSegmentName :: Lens' ImportJobResource (Maybe Text) Source #

A custom name for the segment created by the import job. Use if DefineSegment is true.

ijrFormat :: Lens' ImportJobResource (Maybe DefinitionFormat) Source #

The format of the files that contain the endpoint definitions. Valid values: CSV, JSON

ijrDefineSegment :: Lens' ImportJobResource (Maybe Bool) Source #

Sets whether the endpoints create a segment when they are imported.

ijrRegisterEndpoints :: Lens' ImportJobResource (Maybe Bool) Source #

Sets whether the endpoints are registered with Amazon Pinpoint when they are imported.

ijrExternalId :: Lens' ImportJobResource (Maybe Text) Source #

A unique, custom ID assigned to the IAM role that restricts who can assume the role.

ijrS3URL :: Lens' ImportJobResource (Maybe Text) Source #

A URL that points to the location within an Amazon S3 bucket that contains the endpoints to import. The location can be a folder or a single file. The URL should follow this format: s3:/bucket-namefolder-name/file-name Amazon Pinpoint will import endpoints from this location and any subfolders it contains.

ijrSegmentId :: Lens' ImportJobResource (Maybe Text) Source #

The ID of the segment to update if the import job is meant to update an existing segment.

ijrRoleARN :: Lens' ImportJobResource (Maybe Text) Source #

The Amazon Resource Name (ARN) of an IAM role that grants Amazon Pinpoint access to the Amazon S3 location that contains the endpoints to import.

ImportJobResponse

data ImportJobResponse Source #

See: importJobResponse smart constructor.

Instances

Eq ImportJobResponse Source # 
Data ImportJobResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportJobResponse -> c ImportJobResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportJobResponse #

toConstr :: ImportJobResponse -> Constr #

dataTypeOf :: ImportJobResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImportJobResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportJobResponse) #

gmapT :: (forall b. Data b => b -> b) -> ImportJobResponse -> ImportJobResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportJobResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportJobResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImportJobResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportJobResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportJobResponse -> m ImportJobResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportJobResponse -> m ImportJobResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportJobResponse -> m ImportJobResponse #

Read ImportJobResponse Source # 
Show ImportJobResponse Source # 
Generic ImportJobResponse Source # 
Hashable ImportJobResponse Source # 
FromJSON ImportJobResponse Source # 
NFData ImportJobResponse Source # 

Methods

rnf :: ImportJobResponse -> () #

type Rep ImportJobResponse Source # 
type Rep ImportJobResponse = D1 (MetaData "ImportJobResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "ImportJobResponse'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ijCompletedPieces") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) ((:*:) (S1 (MetaSel (Just Symbol "_ijFailedPieces") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_ijDefinition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ImportJobResource))))) ((:*:) (S1 (MetaSel (Just Symbol "_ijTotalProcessed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) ((:*:) (S1 (MetaSel (Just Symbol "_ijFailures") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_ijTotalPieces") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ijApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ijId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ijCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ijType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ijCompletionDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ijJobStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe JobStatus))) (S1 (MetaSel (Just Symbol "_ijTotalFailures") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))))))

importJobResponse :: ImportJobResponse Source #

Creates a value of ImportJobResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ijCompletedPieces - The number of pieces that have successfully imported as of the time of the request.
  • ijFailedPieces - The number of pieces that have failed to import as of the time of the request.
  • ijDefinition - The import job settings.
  • ijTotalProcessed - The number of endpoints that were processed by the import job.
  • ijFailures - Provides up to 100 of the first failed entries for the job, if any exist.
  • ijTotalPieces - The total number of pieces that must be imported to finish the job. Each piece is an approximately equal portion of the endpoints to import.
  • ijApplicationId - The unique ID of the application to which the import job applies.
  • ijId - The unique ID of the import job.
  • ijCreationDate - The date the import job was created in ISO 8601 format.
  • ijType - The job type. Will be Import.
  • ijCompletionDate - The date the import job completed in ISO 8601 format.
  • ijJobStatus - The status of the import job. Valid values: CREATED, INITIALIZING, PROCESSING, COMPLETING, COMPLETED, FAILING, FAILED The job status is FAILED if one or more pieces failed to import.
  • ijTotalFailures - The number of endpoints that failed to import; for example, because of syntax errors.

ijCompletedPieces :: Lens' ImportJobResponse (Maybe Int) Source #

The number of pieces that have successfully imported as of the time of the request.

ijFailedPieces :: Lens' ImportJobResponse (Maybe Int) Source #

The number of pieces that have failed to import as of the time of the request.

ijTotalProcessed :: Lens' ImportJobResponse (Maybe Int) Source #

The number of endpoints that were processed by the import job.

ijFailures :: Lens' ImportJobResponse [Text] Source #

Provides up to 100 of the first failed entries for the job, if any exist.

ijTotalPieces :: Lens' ImportJobResponse (Maybe Int) Source #

The total number of pieces that must be imported to finish the job. Each piece is an approximately equal portion of the endpoints to import.

ijApplicationId :: Lens' ImportJobResponse (Maybe Text) Source #

The unique ID of the application to which the import job applies.

ijId :: Lens' ImportJobResponse (Maybe Text) Source #

The unique ID of the import job.

ijCreationDate :: Lens' ImportJobResponse (Maybe Text) Source #

The date the import job was created in ISO 8601 format.

ijType :: Lens' ImportJobResponse (Maybe Text) Source #

The job type. Will be Import.

ijCompletionDate :: Lens' ImportJobResponse (Maybe Text) Source #

The date the import job completed in ISO 8601 format.

ijJobStatus :: Lens' ImportJobResponse (Maybe JobStatus) Source #

The status of the import job. Valid values: CREATED, INITIALIZING, PROCESSING, COMPLETING, COMPLETED, FAILING, FAILED The job status is FAILED if one or more pieces failed to import.

ijTotalFailures :: Lens' ImportJobResponse (Maybe Int) Source #

The number of endpoints that failed to import; for example, because of syntax errors.

ImportJobsResponse

data ImportJobsResponse Source #

Import job list.

See: importJobsResponse smart constructor.

Instances

Eq ImportJobsResponse Source # 
Data ImportJobsResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportJobsResponse -> c ImportJobsResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportJobsResponse #

toConstr :: ImportJobsResponse -> Constr #

dataTypeOf :: ImportJobsResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImportJobsResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportJobsResponse) #

gmapT :: (forall b. Data b => b -> b) -> ImportJobsResponse -> ImportJobsResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportJobsResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportJobsResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImportJobsResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportJobsResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportJobsResponse -> m ImportJobsResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportJobsResponse -> m ImportJobsResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportJobsResponse -> m ImportJobsResponse #

Read ImportJobsResponse Source # 
Show ImportJobsResponse Source # 
Generic ImportJobsResponse Source # 
Hashable ImportJobsResponse Source # 
FromJSON ImportJobsResponse Source # 
NFData ImportJobsResponse Source # 

Methods

rnf :: ImportJobsResponse -> () #

type Rep ImportJobsResponse Source # 
type Rep ImportJobsResponse = D1 (MetaData "ImportJobsResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "ImportJobsResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ijNextToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ijItem") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ImportJobResponse])))))

importJobsResponse :: ImportJobsResponse Source #

Creates a value of ImportJobsResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ijNextToken - The string that you use in a subsequent request to get the next page of results in a paginated response.
  • ijItem - A list of import jobs for the application.

ijNextToken :: Lens' ImportJobsResponse (Maybe Text) Source #

The string that you use in a subsequent request to get the next page of results in a paginated response.

ijItem :: Lens' ImportJobsResponse [ImportJobResponse] Source #

A list of import jobs for the application.

Message

data Message Source #

See: message smart constructor.

Instances

Eq Message Source # 

Methods

(==) :: Message -> Message -> Bool #

(/=) :: Message -> Message -> Bool #

Data Message Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Message -> c Message #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Message #

toConstr :: Message -> Constr #

dataTypeOf :: Message -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Message) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Message) #

gmapT :: (forall b. Data b => b -> b) -> Message -> Message #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Message -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Message -> r #

gmapQ :: (forall d. Data d => d -> u) -> Message -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Message -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Message -> m Message #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Message -> m Message #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Message -> m Message #

Read Message Source # 
Show Message Source # 
Generic Message Source # 

Associated Types

type Rep Message :: * -> * #

Methods

from :: Message -> Rep Message x #

to :: Rep Message x -> Message #

Hashable Message Source # 

Methods

hashWithSalt :: Int -> Message -> Int #

hash :: Message -> Int #

FromJSON Message Source # 
ToJSON Message Source # 
NFData Message Source # 

Methods

rnf :: Message -> () #

type Rep Message Source # 

message :: Message Source #

Creates a value of Message with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • mSilentPush - Indicates if the message should display on the users device. Silent pushes can be used for Remote Configuration and Phone Home use cases.
  • mImageIconURL - The URL that points to the icon image for the push notification icon, for example, the app icon.
  • mRawContent - The Raw JSON formatted string to be used as the payload. This value overrides the message.
  • mBody - The message body. Can include up to 140 characters.
  • mImageSmallIconURL - The URL that points to the small icon image for the push notification icon, for example, the app icon.
  • mJSONBody - The JSON payload used for a silent push.
  • mURL - The URL to open in the user's mobile browser. Used if the value for Action is URL.
  • mAction - The action that occurs if the user taps a push notification delivered by the campaign: OPEN_APP - Your app launches, or it becomes the foreground app if it has been sent to the background. This is the default action. DEEP_LINK - Uses deep linking features in iOS and Android to open your app and display a designated user interface within the app. URL - The default mobile browser on the user's device launches and opens a web page at the URL you specify.
  • mImageURL - The URL that points to an image used in the push notification.
  • mMediaURL - The URL that points to the media resource, for example a .mp4 or .gif file.
  • mTitle - The message title that displays above the message on the user's device.

mSilentPush :: Lens' Message (Maybe Bool) Source #

Indicates if the message should display on the users device. Silent pushes can be used for Remote Configuration and Phone Home use cases.

mImageIconURL :: Lens' Message (Maybe Text) Source #

The URL that points to the icon image for the push notification icon, for example, the app icon.

mRawContent :: Lens' Message (Maybe Text) Source #

The Raw JSON formatted string to be used as the payload. This value overrides the message.

mBody :: Lens' Message (Maybe Text) Source #

The message body. Can include up to 140 characters.

mImageSmallIconURL :: Lens' Message (Maybe Text) Source #

The URL that points to the small icon image for the push notification icon, for example, the app icon.

mJSONBody :: Lens' Message (Maybe Text) Source #

The JSON payload used for a silent push.

mURL :: Lens' Message (Maybe Text) Source #

The URL to open in the user's mobile browser. Used if the value for Action is URL.

mAction :: Lens' Message (Maybe Action) Source #

The action that occurs if the user taps a push notification delivered by the campaign: OPEN_APP - Your app launches, or it becomes the foreground app if it has been sent to the background. This is the default action. DEEP_LINK - Uses deep linking features in iOS and Android to open your app and display a designated user interface within the app. URL - The default mobile browser on the user's device launches and opens a web page at the URL you specify.

mImageURL :: Lens' Message (Maybe Text) Source #

The URL that points to an image used in the push notification.

mMediaURL :: Lens' Message (Maybe Text) Source #

The URL that points to the media resource, for example a .mp4 or .gif file.

mTitle :: Lens' Message (Maybe Text) Source #

The message title that displays above the message on the user's device.

MessageBody

data MessageBody Source #

Simple message object.

See: messageBody smart constructor.

Instances

Eq MessageBody Source # 
Data MessageBody Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageBody -> c MessageBody #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageBody #

toConstr :: MessageBody -> Constr #

dataTypeOf :: MessageBody -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MessageBody) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageBody) #

gmapT :: (forall b. Data b => b -> b) -> MessageBody -> MessageBody #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageBody -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageBody -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageBody -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageBody -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageBody -> m MessageBody #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageBody -> m MessageBody #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageBody -> m MessageBody #

Read MessageBody Source # 
Show MessageBody Source # 
Generic MessageBody Source # 

Associated Types

type Rep MessageBody :: * -> * #

Hashable MessageBody Source # 
FromJSON MessageBody Source # 
NFData MessageBody Source # 

Methods

rnf :: MessageBody -> () #

type Rep MessageBody Source # 
type Rep MessageBody = D1 (MetaData "MessageBody" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "MessageBody'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_mbRequestId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_mbMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

messageBody :: MessageBody Source #

Creates a value of MessageBody with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

mbRequestId :: Lens' MessageBody (Maybe Text) Source #

The unique message body ID.

mbMessage :: Lens' MessageBody (Maybe Text) Source #

The error message returned from the API.

MessageConfiguration

data MessageConfiguration Source #

Message configuration for a campaign.

See: messageConfiguration smart constructor.

Instances

Eq MessageConfiguration Source # 
Data MessageConfiguration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageConfiguration -> c MessageConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageConfiguration #

toConstr :: MessageConfiguration -> Constr #

dataTypeOf :: MessageConfiguration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MessageConfiguration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> MessageConfiguration -> MessageConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageConfiguration -> m MessageConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageConfiguration -> m MessageConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageConfiguration -> m MessageConfiguration #

Read MessageConfiguration Source # 
Show MessageConfiguration Source # 
Generic MessageConfiguration Source # 
Hashable MessageConfiguration Source # 
FromJSON MessageConfiguration Source # 
ToJSON MessageConfiguration Source # 
NFData MessageConfiguration Source # 

Methods

rnf :: MessageConfiguration -> () #

type Rep MessageConfiguration Source # 

messageConfiguration :: MessageConfiguration Source #

Creates a value of MessageConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • mcAPNSMessage - The message that the campaign delivers to APNS channels. Overrides the default message.
  • mcGCMMessage - The message that the campaign delivers to GCM channels. Overrides the default message.
  • mcDefaultMessage - The default message for all channels.
  • mcADMMessage - The message that the campaign delivers to ADM channels. Overrides the default message.
  • mcSMSMessage - The SMS message configuration.
  • mcEmailMessage - The email message configuration.
  • mcBaiduMessage - The message that the campaign delivers to Baidu channels. Overrides the default message.

mcAPNSMessage :: Lens' MessageConfiguration (Maybe Message) Source #

The message that the campaign delivers to APNS channels. Overrides the default message.

mcGCMMessage :: Lens' MessageConfiguration (Maybe Message) Source #

The message that the campaign delivers to GCM channels. Overrides the default message.

mcDefaultMessage :: Lens' MessageConfiguration (Maybe Message) Source #

The default message for all channels.

mcADMMessage :: Lens' MessageConfiguration (Maybe Message) Source #

The message that the campaign delivers to ADM channels. Overrides the default message.

mcBaiduMessage :: Lens' MessageConfiguration (Maybe Message) Source #

The message that the campaign delivers to Baidu channels. Overrides the default message.

MessageRequest

data MessageRequest Source #

Send message request.

See: messageRequest smart constructor.

Instances

Eq MessageRequest Source # 
Data MessageRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageRequest -> c MessageRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageRequest #

toConstr :: MessageRequest -> Constr #

dataTypeOf :: MessageRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MessageRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageRequest) #

gmapT :: (forall b. Data b => b -> b) -> MessageRequest -> MessageRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageRequest -> m MessageRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageRequest -> m MessageRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageRequest -> m MessageRequest #

Read MessageRequest Source # 
Show MessageRequest Source # 
Generic MessageRequest Source # 

Associated Types

type Rep MessageRequest :: * -> * #

Hashable MessageRequest Source # 
ToJSON MessageRequest Source # 
NFData MessageRequest Source # 

Methods

rnf :: MessageRequest -> () #

type Rep MessageRequest Source # 
type Rep MessageRequest = D1 (MetaData "MessageRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "MessageRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_mrContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text)))) (S1 (MetaSel (Just Symbol "_mrAddresses") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text AddressConfiguration))))) ((:*:) (S1 (MetaSel (Just Symbol "_mrEndpoints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text EndpointSendConfiguration)))) (S1 (MetaSel (Just Symbol "_mrMessageConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DirectMessageConfiguration))))))

messageRequest :: MessageRequest Source #

Creates a value of MessageRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • mrContext - A map of custom attributes to attributes to be attached to the message. This payload is added to the push notification's 'data.pinpoint' object or added to the email/sms delivery receipt event attributes.
  • mrAddresses - A map of destination addresses, with the address as the key(Email address, phone number or push token) and the Address Configuration as the value.
  • mrEndpoints - A map of destination addresses, with the address as the key(Email address, phone number or push token) and the Address Configuration as the value.
  • mrMessageConfiguration - Message configuration.

mrContext :: Lens' MessageRequest (HashMap Text Text) Source #

A map of custom attributes to attributes to be attached to the message. This payload is added to the push notification's 'data.pinpoint' object or added to the email/sms delivery receipt event attributes.

mrAddresses :: Lens' MessageRequest (HashMap Text AddressConfiguration) Source #

A map of destination addresses, with the address as the key(Email address, phone number or push token) and the Address Configuration as the value.

mrEndpoints :: Lens' MessageRequest (HashMap Text EndpointSendConfiguration) Source #

A map of destination addresses, with the address as the key(Email address, phone number or push token) and the Address Configuration as the value.

MessageResponse

data MessageResponse Source #

Send message response.

See: messageResponse smart constructor.

Instances

Eq MessageResponse Source # 
Data MessageResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageResponse -> c MessageResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageResponse #

toConstr :: MessageResponse -> Constr #

dataTypeOf :: MessageResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MessageResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageResponse) #

gmapT :: (forall b. Data b => b -> b) -> MessageResponse -> MessageResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageResponse -> m MessageResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageResponse -> m MessageResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageResponse -> m MessageResponse #

Read MessageResponse Source # 
Show MessageResponse Source # 
Generic MessageResponse Source # 
Hashable MessageResponse Source # 
FromJSON MessageResponse Source # 
NFData MessageResponse Source # 

Methods

rnf :: MessageResponse -> () #

type Rep MessageResponse Source # 
type Rep MessageResponse = D1 (MetaData "MessageResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "MessageResponse'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_mRequestId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_mResult") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text MessageResult))))) ((:*:) (S1 (MetaSel (Just Symbol "_mApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_mEndpointResult") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text EndpointMessageResult)))))))

messageResponse :: MessageResponse Source #

Creates a value of MessageResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • mRequestId - Original request Id for which this message was delivered.
  • mResult - A map containing a multi part response for each address, with the address as the key(Email address, phone number or push token) and the result as the value.
  • mApplicationId - Application id of the message.
  • mEndpointResult - A map containing a multi part response for each address, with the endpointId as the key and the result as the value.

mRequestId :: Lens' MessageResponse (Maybe Text) Source #

Original request Id for which this message was delivered.

mResult :: Lens' MessageResponse (HashMap Text MessageResult) Source #

A map containing a multi part response for each address, with the address as the key(Email address, phone number or push token) and the result as the value.

mApplicationId :: Lens' MessageResponse (Maybe Text) Source #

Application id of the message.

mEndpointResult :: Lens' MessageResponse (HashMap Text EndpointMessageResult) Source #

A map containing a multi part response for each address, with the endpointId as the key and the result as the value.

MessageResult

data MessageResult Source #

The result from sending a message to an address.

See: messageResult smart constructor.

Instances

Eq MessageResult Source # 
Data MessageResult Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageResult -> c MessageResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageResult #

toConstr :: MessageResult -> Constr #

dataTypeOf :: MessageResult -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MessageResult) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageResult) #

gmapT :: (forall b. Data b => b -> b) -> MessageResult -> MessageResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageResult -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageResult -> m MessageResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageResult -> m MessageResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageResult -> m MessageResult #

Read MessageResult Source # 
Show MessageResult Source # 
Generic MessageResult Source # 

Associated Types

type Rep MessageResult :: * -> * #

Hashable MessageResult Source # 
FromJSON MessageResult Source # 
NFData MessageResult Source # 

Methods

rnf :: MessageResult -> () #

type Rep MessageResult Source # 
type Rep MessageResult = D1 (MetaData "MessageResult" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "MessageResult'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_mrDeliveryStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeliveryStatus))) (S1 (MetaSel (Just Symbol "_mrStatusMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_mrUpdatedToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_mrStatusCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))))

messageResult :: MessageResult Source #

Creates a value of MessageResult with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

mrStatusMessage :: Lens' MessageResult (Maybe Text) Source #

Status message for message delivery.

mrUpdatedToken :: Lens' MessageResult (Maybe Text) Source #

If token was updated as part of delivery. (This is GCM Specific)

mrStatusCode :: Lens' MessageResult (Maybe Int) Source #

Downstream service status code.

QuietTime

data QuietTime Source #

Quiet Time

See: quietTime smart constructor.

Instances

Eq QuietTime Source # 
Data QuietTime Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QuietTime -> c QuietTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QuietTime #

toConstr :: QuietTime -> Constr #

dataTypeOf :: QuietTime -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c QuietTime) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuietTime) #

gmapT :: (forall b. Data b => b -> b) -> QuietTime -> QuietTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QuietTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QuietTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> QuietTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QuietTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QuietTime -> m QuietTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QuietTime -> m QuietTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QuietTime -> m QuietTime #

Read QuietTime Source # 
Show QuietTime Source # 
Generic QuietTime Source # 

Associated Types

type Rep QuietTime :: * -> * #

Hashable QuietTime Source # 
FromJSON QuietTime Source # 
ToJSON QuietTime Source # 
NFData QuietTime Source # 

Methods

rnf :: QuietTime -> () #

type Rep QuietTime Source # 
type Rep QuietTime = D1 (MetaData "QuietTime" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "QuietTime'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_qtStart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_qtEnd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

quietTime :: QuietTime Source #

Creates a value of QuietTime with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • qtStart - The default start time for quiet time in ISO 8601 format.
  • qtEnd - The default end time for quiet time in ISO 8601 format.

qtStart :: Lens' QuietTime (Maybe Text) Source #

The default start time for quiet time in ISO 8601 format.

qtEnd :: Lens' QuietTime (Maybe Text) Source #

The default end time for quiet time in ISO 8601 format.

RecencyDimension

data RecencyDimension Source #

Define how a segment based on recency of use.

See: recencyDimension smart constructor.

Instances

Eq RecencyDimension Source # 
Data RecencyDimension Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecencyDimension -> c RecencyDimension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecencyDimension #

toConstr :: RecencyDimension -> Constr #

dataTypeOf :: RecencyDimension -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RecencyDimension) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecencyDimension) #

gmapT :: (forall b. Data b => b -> b) -> RecencyDimension -> RecencyDimension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecencyDimension -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecencyDimension -> r #

gmapQ :: (forall d. Data d => d -> u) -> RecencyDimension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RecencyDimension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecencyDimension -> m RecencyDimension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecencyDimension -> m RecencyDimension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecencyDimension -> m RecencyDimension #

Read RecencyDimension Source # 
Show RecencyDimension Source # 
Generic RecencyDimension Source # 
Hashable RecencyDimension Source # 
FromJSON RecencyDimension Source # 
ToJSON RecencyDimension Source # 
NFData RecencyDimension Source # 

Methods

rnf :: RecencyDimension -> () #

type Rep RecencyDimension Source # 
type Rep RecencyDimension = D1 (MetaData "RecencyDimension" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "RecencyDimension'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rdRecencyType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RecencyType))) (S1 (MetaSel (Just Symbol "_rdDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Duration)))))

recencyDimension :: RecencyDimension Source #

Creates a value of RecencyDimension with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rdRecencyType - The recency dimension type: ACTIVE - Users who have used your app within the specified duration are included in the segment. INACTIVE - Users who have not used your app within the specified duration are included in the segment.
  • rdDuration - The length of time during which users have been active or inactive with your app. Valid values: HR_24, DAY_7, DAY_14, DAY_30

rdRecencyType :: Lens' RecencyDimension (Maybe RecencyType) Source #

The recency dimension type: ACTIVE - Users who have used your app within the specified duration are included in the segment. INACTIVE - Users who have not used your app within the specified duration are included in the segment.

rdDuration :: Lens' RecencyDimension (Maybe Duration) Source #

The length of time during which users have been active or inactive with your app. Valid values: HR_24, DAY_7, DAY_14, DAY_30

SMSChannelRequest

data SMSChannelRequest Source #

SMS Channel Request

See: sMSChannelRequest smart constructor.

Instances

Eq SMSChannelRequest Source # 
Data SMSChannelRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SMSChannelRequest -> c SMSChannelRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SMSChannelRequest #

toConstr :: SMSChannelRequest -> Constr #

dataTypeOf :: SMSChannelRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SMSChannelRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SMSChannelRequest) #

gmapT :: (forall b. Data b => b -> b) -> SMSChannelRequest -> SMSChannelRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SMSChannelRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SMSChannelRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> SMSChannelRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SMSChannelRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SMSChannelRequest -> m SMSChannelRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SMSChannelRequest -> m SMSChannelRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SMSChannelRequest -> m SMSChannelRequest #

Read SMSChannelRequest Source # 
Show SMSChannelRequest Source # 
Generic SMSChannelRequest Source # 
Hashable SMSChannelRequest Source # 
ToJSON SMSChannelRequest Source # 
NFData SMSChannelRequest Source # 

Methods

rnf :: SMSChannelRequest -> () #

type Rep SMSChannelRequest Source # 
type Rep SMSChannelRequest = D1 (MetaData "SMSChannelRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "SMSChannelRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_smscrShortCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_smscrEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_smscrSenderId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

sMSChannelRequest :: SMSChannelRequest Source #

Creates a value of SMSChannelRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

smscrShortCode :: Lens' SMSChannelRequest (Maybe Text) Source #

ShortCode registered with phone provider.

smscrEnabled :: Lens' SMSChannelRequest (Maybe Bool) Source #

If the channel is enabled for sending messages.

smscrSenderId :: Lens' SMSChannelRequest (Maybe Text) Source #

Sender identifier of your messages.

SMSChannelResponse

data SMSChannelResponse Source #

SMS Channel Response.

See: sMSChannelResponse smart constructor.

Instances

Eq SMSChannelResponse Source # 
Data SMSChannelResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SMSChannelResponse -> c SMSChannelResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SMSChannelResponse #

toConstr :: SMSChannelResponse -> Constr #

dataTypeOf :: SMSChannelResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SMSChannelResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SMSChannelResponse) #

gmapT :: (forall b. Data b => b -> b) -> SMSChannelResponse -> SMSChannelResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SMSChannelResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SMSChannelResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> SMSChannelResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SMSChannelResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SMSChannelResponse -> m SMSChannelResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SMSChannelResponse -> m SMSChannelResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SMSChannelResponse -> m SMSChannelResponse #

Read SMSChannelResponse Source # 
Show SMSChannelResponse Source # 
Generic SMSChannelResponse Source # 
Hashable SMSChannelResponse Source # 
FromJSON SMSChannelResponse Source # 
NFData SMSChannelResponse Source # 

Methods

rnf :: SMSChannelResponse -> () #

type Rep SMSChannelResponse Source # 
type Rep SMSChannelResponse = D1 (MetaData "SMSChannelResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "SMSChannelResponse'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_smscPlatform") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_smscShortCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_smscLastModifiedDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_smscEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_smscSenderId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_smscIsArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_smscApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_smscVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_smscId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_smscCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_smscLastModifiedBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_smscHasCredential") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))))

sMSChannelResponse :: SMSChannelResponse Source #

Creates a value of SMSChannelResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

smscShortCode :: Lens' SMSChannelResponse (Maybe Text) Source #

The short code registered with the phone provider.

smscEnabled :: Lens' SMSChannelResponse (Maybe Bool) Source #

If the channel is enabled for sending messages.

smscSenderId :: Lens' SMSChannelResponse (Maybe Text) Source #

Sender identifier of your messages.

smscApplicationId :: Lens' SMSChannelResponse (Maybe Text) Source #

The unique ID of the application to which the SMS channel belongs.

smscId :: Lens' SMSChannelResponse (Maybe Text) Source #

Channel ID. Not used, only for backwards compatibility.

smscCreationDate :: Lens' SMSChannelResponse (Maybe Text) Source #

The date that the settings were last updated in ISO 8601 format.

smscLastModifiedBy :: Lens' SMSChannelResponse (Maybe Text) Source #

Who last updated this entry

smscHasCredential :: Lens' SMSChannelResponse (Maybe Bool) Source #

If the channel is registered with a credential for authentication.

SMSMessage

data SMSMessage Source #

SMS Message.

See: sMSMessage smart constructor.

Instances

Eq SMSMessage Source # 
Data SMSMessage Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SMSMessage -> c SMSMessage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SMSMessage #

toConstr :: SMSMessage -> Constr #

dataTypeOf :: SMSMessage -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SMSMessage) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SMSMessage) #

gmapT :: (forall b. Data b => b -> b) -> SMSMessage -> SMSMessage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SMSMessage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SMSMessage -> r #

gmapQ :: (forall d. Data d => d -> u) -> SMSMessage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SMSMessage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SMSMessage -> m SMSMessage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SMSMessage -> m SMSMessage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SMSMessage -> m SMSMessage #

Read SMSMessage Source # 
Show SMSMessage Source # 
Generic SMSMessage Source # 

Associated Types

type Rep SMSMessage :: * -> * #

Hashable SMSMessage Source # 
ToJSON SMSMessage Source # 
NFData SMSMessage Source # 

Methods

rnf :: SMSMessage -> () #

type Rep SMSMessage Source # 
type Rep SMSMessage = D1 (MetaData "SMSMessage" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "SMSMessage'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_smsmSubstitutions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text [Text])))) (S1 (MetaSel (Just Symbol "_smsmBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_smsmMessageType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MessageType))) (S1 (MetaSel (Just Symbol "_smsmSenderId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

sMSMessage :: SMSMessage Source #

Creates a value of SMSMessage with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • smsmSubstitutions - Default message substitutions. Can be overridden by individual address substitutions.
  • smsmBody - The message body of the notification, the email body or the text message.
  • smsmMessageType - Is this a transaction priority message or lower priority.
  • smsmSenderId - Sender ID of sent message.

smsmSubstitutions :: Lens' SMSMessage (HashMap Text [Text]) Source #

Default message substitutions. Can be overridden by individual address substitutions.

smsmBody :: Lens' SMSMessage (Maybe Text) Source #

The message body of the notification, the email body or the text message.

smsmMessageType :: Lens' SMSMessage (Maybe MessageType) Source #

Is this a transaction priority message or lower priority.

smsmSenderId :: Lens' SMSMessage (Maybe Text) Source #

Sender ID of sent message.

Schedule

data Schedule Source #

Shcedule that defines when a campaign is run.

See: schedule smart constructor.

Instances

Eq Schedule Source # 
Data Schedule Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Schedule -> c Schedule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Schedule #

toConstr :: Schedule -> Constr #

dataTypeOf :: Schedule -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Schedule) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Schedule) #

gmapT :: (forall b. Data b => b -> b) -> Schedule -> Schedule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Schedule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Schedule -> r #

gmapQ :: (forall d. Data d => d -> u) -> Schedule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Schedule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Schedule -> m Schedule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Schedule -> m Schedule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Schedule -> m Schedule #

Read Schedule Source # 
Show Schedule Source # 
Generic Schedule Source # 

Associated Types

type Rep Schedule :: * -> * #

Methods

from :: Schedule -> Rep Schedule x #

to :: Rep Schedule x -> Schedule #

Hashable Schedule Source # 

Methods

hashWithSalt :: Int -> Schedule -> Int #

hash :: Schedule -> Int #

FromJSON Schedule Source # 
ToJSON Schedule Source # 
NFData Schedule Source # 

Methods

rnf :: Schedule -> () #

type Rep Schedule Source # 

schedule :: Schedule Source #

Creates a value of Schedule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sFrequency - How often the campaign delivers messages. Valid values: ONCE, HOURLY, DAILY, WEEKLY, MONTHLY
  • sStartTime - The scheduled time that the campaign begins in ISO 8601 format.
  • sQuietTime - The time during which the campaign sends no messages.
  • sIsLocalTime - Indicates whether the campaign schedule takes effect according to each user's local time.
  • sEndTime - The scheduled time that the campaign ends in ISO 8601 format.
  • sTimezone - The starting UTC offset for the schedule if the value for isLocalTime is true Valid values: UTC UTC+01 UTC+02 UTC+03 UTC+03:30 UTC+04 UTC+04:30 UTC+05 UTC+05:30 UTC+05:45 UTC+06 UTC+06:30 UTC+07 UTC+08 UTC+09 UTC+09:30 UTC+10 UTC+10:30 UTC+11 UTC+12 UTC+13 UTC-02 UTC-03 UTC-04 UTC-05 UTC-06 UTC-07 UTC-08 UTC-09 UTC-10 UTC-11

sFrequency :: Lens' Schedule (Maybe Frequency) Source #

How often the campaign delivers messages. Valid values: ONCE, HOURLY, DAILY, WEEKLY, MONTHLY

sStartTime :: Lens' Schedule (Maybe Text) Source #

The scheduled time that the campaign begins in ISO 8601 format.

sQuietTime :: Lens' Schedule (Maybe QuietTime) Source #

The time during which the campaign sends no messages.

sIsLocalTime :: Lens' Schedule (Maybe Bool) Source #

Indicates whether the campaign schedule takes effect according to each user's local time.

sEndTime :: Lens' Schedule (Maybe Text) Source #

The scheduled time that the campaign ends in ISO 8601 format.

sTimezone :: Lens' Schedule (Maybe Text) Source #

The starting UTC offset for the schedule if the value for isLocalTime is true Valid values: UTC UTC+01 UTC+02 UTC+03 UTC+03:30 UTC+04 UTC+04:30 UTC+05 UTC+05:30 UTC+05:45 UTC+06 UTC+06:30 UTC+07 UTC+08 UTC+09 UTC+09:30 UTC+10 UTC+10:30 UTC+11 UTC+12 UTC+13 UTC-02 UTC-03 UTC-04 UTC-05 UTC-06 UTC-07 UTC-08 UTC-09 UTC-10 UTC-11

SegmentBehaviors

data SegmentBehaviors Source #

Segment behavior dimensions

See: segmentBehaviors smart constructor.

Instances

Eq SegmentBehaviors Source # 
Data SegmentBehaviors Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SegmentBehaviors -> c SegmentBehaviors #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SegmentBehaviors #

toConstr :: SegmentBehaviors -> Constr #

dataTypeOf :: SegmentBehaviors -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SegmentBehaviors) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SegmentBehaviors) #

gmapT :: (forall b. Data b => b -> b) -> SegmentBehaviors -> SegmentBehaviors #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SegmentBehaviors -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SegmentBehaviors -> r #

gmapQ :: (forall d. Data d => d -> u) -> SegmentBehaviors -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SegmentBehaviors -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SegmentBehaviors -> m SegmentBehaviors #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentBehaviors -> m SegmentBehaviors #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentBehaviors -> m SegmentBehaviors #

Read SegmentBehaviors Source # 
Show SegmentBehaviors Source # 
Generic SegmentBehaviors Source # 
Hashable SegmentBehaviors Source # 
FromJSON SegmentBehaviors Source # 
ToJSON SegmentBehaviors Source # 
NFData SegmentBehaviors Source # 

Methods

rnf :: SegmentBehaviors -> () #

type Rep SegmentBehaviors Source # 
type Rep SegmentBehaviors = D1 (MetaData "SegmentBehaviors" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" True) (C1 (MetaCons "SegmentBehaviors'" PrefixI True) (S1 (MetaSel (Just Symbol "_sbRecency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe RecencyDimension))))

segmentBehaviors :: SegmentBehaviors Source #

Creates a value of SegmentBehaviors with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

SegmentDemographics

data SegmentDemographics Source #

Segment demographic dimensions

See: segmentDemographics smart constructor.

Instances

Eq SegmentDemographics Source # 
Data SegmentDemographics Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SegmentDemographics -> c SegmentDemographics #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SegmentDemographics #

toConstr :: SegmentDemographics -> Constr #

dataTypeOf :: SegmentDemographics -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SegmentDemographics) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SegmentDemographics) #

gmapT :: (forall b. Data b => b -> b) -> SegmentDemographics -> SegmentDemographics #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SegmentDemographics -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SegmentDemographics -> r #

gmapQ :: (forall d. Data d => d -> u) -> SegmentDemographics -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SegmentDemographics -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SegmentDemographics -> m SegmentDemographics #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentDemographics -> m SegmentDemographics #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentDemographics -> m SegmentDemographics #

Read SegmentDemographics Source # 
Show SegmentDemographics Source # 
Generic SegmentDemographics Source # 
Hashable SegmentDemographics Source # 
FromJSON SegmentDemographics Source # 
ToJSON SegmentDemographics Source # 
NFData SegmentDemographics Source # 

Methods

rnf :: SegmentDemographics -> () #

type Rep SegmentDemographics Source # 

segmentDemographics :: SegmentDemographics Source #

Creates a value of SegmentDemographics with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sdPlatform - The device platform criteria for the segment.
  • sdAppVersion - The app version criteria for the segment.
  • sdChannel - The channel criteria for the segment.
  • sdModel - The device model criteria for the segment.
  • sdMake - The device make criteria for the segment.
  • sdDeviceType - The device type criteria for the segment.

sdPlatform :: Lens' SegmentDemographics (Maybe SetDimension) Source #

The device platform criteria for the segment.

sdAppVersion :: Lens' SegmentDemographics (Maybe SetDimension) Source #

The app version criteria for the segment.

sdChannel :: Lens' SegmentDemographics (Maybe SetDimension) Source #

The channel criteria for the segment.

sdModel :: Lens' SegmentDemographics (Maybe SetDimension) Source #

The device model criteria for the segment.

sdMake :: Lens' SegmentDemographics (Maybe SetDimension) Source #

The device make criteria for the segment.

sdDeviceType :: Lens' SegmentDemographics (Maybe SetDimension) Source #

The device type criteria for the segment.

SegmentDimensions

data SegmentDimensions Source #

Segment dimensions

See: segmentDimensions smart constructor.

Instances

Eq SegmentDimensions Source # 
Data SegmentDimensions Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SegmentDimensions -> c SegmentDimensions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SegmentDimensions #

toConstr :: SegmentDimensions -> Constr #

dataTypeOf :: SegmentDimensions -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SegmentDimensions) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SegmentDimensions) #

gmapT :: (forall b. Data b => b -> b) -> SegmentDimensions -> SegmentDimensions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SegmentDimensions -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SegmentDimensions -> r #

gmapQ :: (forall d. Data d => d -> u) -> SegmentDimensions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SegmentDimensions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SegmentDimensions -> m SegmentDimensions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentDimensions -> m SegmentDimensions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentDimensions -> m SegmentDimensions #

Read SegmentDimensions Source # 
Show SegmentDimensions Source # 
Generic SegmentDimensions Source # 
Hashable SegmentDimensions Source # 
FromJSON SegmentDimensions Source # 
ToJSON SegmentDimensions Source # 
NFData SegmentDimensions Source # 

Methods

rnf :: SegmentDimensions -> () #

type Rep SegmentDimensions Source # 

segmentDimensions :: SegmentDimensions Source #

Creates a value of SegmentDimensions with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sdLocation :: Lens' SegmentDimensions (Maybe SegmentLocation) Source #

The segment location attributes.

sdDemographic :: Lens' SegmentDimensions (Maybe SegmentDemographics) Source #

The segment demographics attributes.

sdBehavior :: Lens' SegmentDimensions (Maybe SegmentBehaviors) Source #

The segment behaviors attributes.

SegmentImportResource

data SegmentImportResource Source #

Segment import definition.

See: segmentImportResource smart constructor.

Instances

Eq SegmentImportResource Source # 
Data SegmentImportResource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SegmentImportResource -> c SegmentImportResource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SegmentImportResource #

toConstr :: SegmentImportResource -> Constr #

dataTypeOf :: SegmentImportResource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SegmentImportResource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SegmentImportResource) #

gmapT :: (forall b. Data b => b -> b) -> SegmentImportResource -> SegmentImportResource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SegmentImportResource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SegmentImportResource -> r #

gmapQ :: (forall d. Data d => d -> u) -> SegmentImportResource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SegmentImportResource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SegmentImportResource -> m SegmentImportResource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentImportResource -> m SegmentImportResource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentImportResource -> m SegmentImportResource #

Read SegmentImportResource Source # 
Show SegmentImportResource Source # 
Generic SegmentImportResource Source # 
Hashable SegmentImportResource Source # 
FromJSON SegmentImportResource Source # 
NFData SegmentImportResource Source # 

Methods

rnf :: SegmentImportResource -> () #

type Rep SegmentImportResource Source # 
type Rep SegmentImportResource = D1 (MetaData "SegmentImportResource" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "SegmentImportResource'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sirSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) ((:*:) (S1 (MetaSel (Just Symbol "_sirFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DefinitionFormat))) (S1 (MetaSel (Just Symbol "_sirChannelCounts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Int)))))) ((:*:) (S1 (MetaSel (Just Symbol "_sirExternalId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sirS3URL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_sirRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

segmentImportResource :: SegmentImportResource Source #

Creates a value of SegmentImportResource with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sirSize - The number of endpoints that were successfully imported to create this segment.
  • sirFormat - The format of the endpoint files that were imported to create this segment. Valid values: CSV, JSON
  • sirChannelCounts - Channel type counts
  • sirExternalId - A unique, custom ID assigned to the IAM role that restricts who can assume the role.
  • sirS3URL - A URL that points to the Amazon S3 location from which the endpoints for this segment were imported.
  • sirRoleARN - The Amazon Resource Name (ARN) of an IAM role that grants Amazon Pinpoint access to the endpoints in Amazon S3.

sirSize :: Lens' SegmentImportResource (Maybe Int) Source #

The number of endpoints that were successfully imported to create this segment.

sirFormat :: Lens' SegmentImportResource (Maybe DefinitionFormat) Source #

The format of the endpoint files that were imported to create this segment. Valid values: CSV, JSON

sirExternalId :: Lens' SegmentImportResource (Maybe Text) Source #

A unique, custom ID assigned to the IAM role that restricts who can assume the role.

sirS3URL :: Lens' SegmentImportResource (Maybe Text) Source #

A URL that points to the Amazon S3 location from which the endpoints for this segment were imported.

sirRoleARN :: Lens' SegmentImportResource (Maybe Text) Source #

The Amazon Resource Name (ARN) of an IAM role that grants Amazon Pinpoint access to the endpoints in Amazon S3.

SegmentLocation

data SegmentLocation Source #

Segment location dimensions

See: segmentLocation smart constructor.

Instances

Eq SegmentLocation Source # 
Data SegmentLocation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SegmentLocation -> c SegmentLocation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SegmentLocation #

toConstr :: SegmentLocation -> Constr #

dataTypeOf :: SegmentLocation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SegmentLocation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SegmentLocation) #

gmapT :: (forall b. Data b => b -> b) -> SegmentLocation -> SegmentLocation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SegmentLocation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SegmentLocation -> r #

gmapQ :: (forall d. Data d => d -> u) -> SegmentLocation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SegmentLocation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SegmentLocation -> m SegmentLocation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentLocation -> m SegmentLocation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentLocation -> m SegmentLocation #

Read SegmentLocation Source # 
Show SegmentLocation Source # 
Generic SegmentLocation Source # 
Hashable SegmentLocation Source # 
FromJSON SegmentLocation Source # 
ToJSON SegmentLocation Source # 
NFData SegmentLocation Source # 

Methods

rnf :: SegmentLocation -> () #

type Rep SegmentLocation Source # 
type Rep SegmentLocation = D1 (MetaData "SegmentLocation" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" True) (C1 (MetaCons "SegmentLocation'" PrefixI True) (S1 (MetaSel (Just Symbol "_slCountry") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SetDimension))))

segmentLocation :: SegmentLocation Source #

Creates a value of SegmentLocation with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • slCountry - The country filter according to ISO 3166-1 Alpha-2 codes.

slCountry :: Lens' SegmentLocation (Maybe SetDimension) Source #

The country filter according to ISO 3166-1 Alpha-2 codes.

SegmentResponse

data SegmentResponse Source #

Segment definition.

See: segmentResponse smart constructor.

Instances

Eq SegmentResponse Source # 
Data SegmentResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SegmentResponse -> c SegmentResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SegmentResponse #

toConstr :: SegmentResponse -> Constr #

dataTypeOf :: SegmentResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SegmentResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SegmentResponse) #

gmapT :: (forall b. Data b => b -> b) -> SegmentResponse -> SegmentResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SegmentResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SegmentResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> SegmentResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SegmentResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SegmentResponse -> m SegmentResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentResponse -> m SegmentResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentResponse -> m SegmentResponse #

Read SegmentResponse Source # 
Show SegmentResponse Source # 
Generic SegmentResponse Source # 
Hashable SegmentResponse Source # 
FromJSON SegmentResponse Source # 
NFData SegmentResponse Source # 

Methods

rnf :: SegmentResponse -> () #

type Rep SegmentResponse Source # 

segmentResponse :: SegmentResponse Source #

Creates a value of SegmentResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sLastModifiedDate - The date the segment was last updated in ISO 8601 format.
  • sSegmentType - The segment type: DIMENSIONAL - A dynamic segment built from selection criteria based on endpoint data reported by your app. You create this type of segment by using the segment builder in the Amazon Pinpoint console or by making a POST request to the segments resource. IMPORT - A static segment built from an imported set of endpoint definitions. You create this type of segment by importing a segment in the Amazon Pinpoint console or by making a POST request to the jobs/import resource.
  • sApplicationId - The ID of the application to which the segment applies.
  • sName - The name of segment
  • sVersion - The segment version number.
  • sId - The unique segment ID.
  • sCreationDate - The date the segment was created in ISO 8601 format.
  • sImportDefinition - The import job settings.
  • sDimensions - The segment dimensions attributes.

sLastModifiedDate :: Lens' SegmentResponse (Maybe Text) Source #

The date the segment was last updated in ISO 8601 format.

sSegmentType :: Lens' SegmentResponse (Maybe SegmentType) Source #

The segment type: DIMENSIONAL - A dynamic segment built from selection criteria based on endpoint data reported by your app. You create this type of segment by using the segment builder in the Amazon Pinpoint console or by making a POST request to the segments resource. IMPORT - A static segment built from an imported set of endpoint definitions. You create this type of segment by importing a segment in the Amazon Pinpoint console or by making a POST request to the jobs/import resource.

sApplicationId :: Lens' SegmentResponse (Maybe Text) Source #

The ID of the application to which the segment applies.

sName :: Lens' SegmentResponse (Maybe Text) Source #

The name of segment

sVersion :: Lens' SegmentResponse (Maybe Int) Source #

The segment version number.

sId :: Lens' SegmentResponse (Maybe Text) Source #

The unique segment ID.

sCreationDate :: Lens' SegmentResponse (Maybe Text) Source #

The date the segment was created in ISO 8601 format.

sDimensions :: Lens' SegmentResponse (Maybe SegmentDimensions) Source #

The segment dimensions attributes.

SegmentsResponse

data SegmentsResponse Source #

Segments in your account.

See: segmentsResponse smart constructor.

Instances

Eq SegmentsResponse Source # 
Data SegmentsResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SegmentsResponse -> c SegmentsResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SegmentsResponse #

toConstr :: SegmentsResponse -> Constr #

dataTypeOf :: SegmentsResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SegmentsResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SegmentsResponse) #

gmapT :: (forall b. Data b => b -> b) -> SegmentsResponse -> SegmentsResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SegmentsResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SegmentsResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> SegmentsResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SegmentsResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SegmentsResponse -> m SegmentsResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentsResponse -> m SegmentsResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentsResponse -> m SegmentsResponse #

Read SegmentsResponse Source # 
Show SegmentsResponse Source # 
Generic SegmentsResponse Source # 
Hashable SegmentsResponse Source # 
FromJSON SegmentsResponse Source # 
NFData SegmentsResponse Source # 

Methods

rnf :: SegmentsResponse -> () #

type Rep SegmentsResponse Source # 
type Rep SegmentsResponse = D1 (MetaData "SegmentsResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "SegmentsResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sNextToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_sItem") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SegmentResponse])))))

segmentsResponse :: SegmentsResponse Source #

Creates a value of SegmentsResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sNextToken - An identifier used to retrieve the next page of results. The token is null if no additional pages exist.
  • sItem - The list of segments.

sNextToken :: Lens' SegmentsResponse (Maybe Text) Source #

An identifier used to retrieve the next page of results. The token is null if no additional pages exist.

SendUsersMessageRequest

data SendUsersMessageRequest Source #

Send message request.

See: sendUsersMessageRequest smart constructor.

Instances

Eq SendUsersMessageRequest Source # 
Data SendUsersMessageRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SendUsersMessageRequest -> c SendUsersMessageRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SendUsersMessageRequest #

toConstr :: SendUsersMessageRequest -> Constr #

dataTypeOf :: SendUsersMessageRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SendUsersMessageRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SendUsersMessageRequest) #

gmapT :: (forall b. Data b => b -> b) -> SendUsersMessageRequest -> SendUsersMessageRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SendUsersMessageRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SendUsersMessageRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> SendUsersMessageRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SendUsersMessageRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SendUsersMessageRequest -> m SendUsersMessageRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SendUsersMessageRequest -> m SendUsersMessageRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SendUsersMessageRequest -> m SendUsersMessageRequest #

Read SendUsersMessageRequest Source # 
Show SendUsersMessageRequest Source # 
Generic SendUsersMessageRequest Source # 
Hashable SendUsersMessageRequest Source # 
ToJSON SendUsersMessageRequest Source # 
NFData SendUsersMessageRequest Source # 

Methods

rnf :: SendUsersMessageRequest -> () #

type Rep SendUsersMessageRequest Source # 
type Rep SendUsersMessageRequest = D1 (MetaData "SendUsersMessageRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "SendUsersMessageRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sumrContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_sumrUsers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text EndpointSendConfiguration)))) (S1 (MetaSel (Just Symbol "_sumrMessageConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DirectMessageConfiguration))))))

sendUsersMessageRequest :: SendUsersMessageRequest Source #

Creates a value of SendUsersMessageRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sumrContext - A map of custom attributes to attributes to be attached to the message. This payload is added to the push notification's 'data.pinpoint' object or added to the email/sms delivery receipt event attributes.
  • sumrUsers - A map of destination endpoints, with the EndpointId as the key Endpoint Message Configuration as the value.
  • sumrMessageConfiguration - Message configuration.

sumrContext :: Lens' SendUsersMessageRequest (HashMap Text Text) Source #

A map of custom attributes to attributes to be attached to the message. This payload is added to the push notification's 'data.pinpoint' object or added to the email/sms delivery receipt event attributes.

sumrUsers :: Lens' SendUsersMessageRequest (HashMap Text EndpointSendConfiguration) Source #

A map of destination endpoints, with the EndpointId as the key Endpoint Message Configuration as the value.

SendUsersMessageResponse

data SendUsersMessageResponse Source #

User send message response.

See: sendUsersMessageResponse smart constructor.

Instances

Eq SendUsersMessageResponse Source # 
Data SendUsersMessageResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SendUsersMessageResponse -> c SendUsersMessageResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SendUsersMessageResponse #

toConstr :: SendUsersMessageResponse -> Constr #

dataTypeOf :: SendUsersMessageResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SendUsersMessageResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SendUsersMessageResponse) #

gmapT :: (forall b. Data b => b -> b) -> SendUsersMessageResponse -> SendUsersMessageResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SendUsersMessageResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SendUsersMessageResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> SendUsersMessageResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SendUsersMessageResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SendUsersMessageResponse -> m SendUsersMessageResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SendUsersMessageResponse -> m SendUsersMessageResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SendUsersMessageResponse -> m SendUsersMessageResponse #

Read SendUsersMessageResponse Source # 
Show SendUsersMessageResponse Source # 
Generic SendUsersMessageResponse Source # 
Hashable SendUsersMessageResponse Source # 
FromJSON SendUsersMessageResponse Source # 
NFData SendUsersMessageResponse Source # 
type Rep SendUsersMessageResponse Source # 
type Rep SendUsersMessageResponse = D1 (MetaData "SendUsersMessageResponse" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "SendUsersMessageResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sumRequestId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sumResult") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text (Map Text EndpointMessageResult))))) (S1 (MetaSel (Just Symbol "_sumApplicationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

sendUsersMessageResponse :: SendUsersMessageResponse Source #

Creates a value of SendUsersMessageResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sumRequestId - Original request Id for which this message was delivered.
  • sumResult - A map containing of UserId to Map of EndpointId to Endpoint Message Result.
  • sumApplicationId - Application id of the message.

sumRequestId :: Lens' SendUsersMessageResponse (Maybe Text) Source #

Original request Id for which this message was delivered.

sumResult :: Lens' SendUsersMessageResponse (HashMap Text (HashMap Text EndpointMessageResult)) Source #

A map containing of UserId to Map of EndpointId to Endpoint Message Result.

sumApplicationId :: Lens' SendUsersMessageResponse (Maybe Text) Source #

Application id of the message.

SetDimension

data SetDimension Source #

Dimension specification of a segment.

See: setDimension smart constructor.

Instances

Eq SetDimension Source # 
Data SetDimension Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SetDimension -> c SetDimension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SetDimension #

toConstr :: SetDimension -> Constr #

dataTypeOf :: SetDimension -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SetDimension) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetDimension) #

gmapT :: (forall b. Data b => b -> b) -> SetDimension -> SetDimension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SetDimension -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SetDimension -> r #

gmapQ :: (forall d. Data d => d -> u) -> SetDimension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SetDimension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SetDimension -> m SetDimension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SetDimension -> m SetDimension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SetDimension -> m SetDimension #

Read SetDimension Source # 
Show SetDimension Source # 
Generic SetDimension Source # 

Associated Types

type Rep SetDimension :: * -> * #

Hashable SetDimension Source # 
FromJSON SetDimension Source # 
ToJSON SetDimension Source # 
NFData SetDimension Source # 

Methods

rnf :: SetDimension -> () #

type Rep SetDimension Source # 
type Rep SetDimension = D1 (MetaData "SetDimension" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "SetDimension'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sdValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_sdDimensionType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionType)))))

setDimension :: SetDimension Source #

Creates a value of SetDimension with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sdValues - The criteria values for the segment dimension. Endpoints with matching attribute values are included or excluded from the segment, depending on the setting for Type.
  • sdDimensionType - The type of dimension: INCLUSIVE - Endpoints that match the criteria are included in the segment. EXCLUSIVE - Endpoints that match the criteria are excluded from the segment.

sdValues :: Lens' SetDimension [Text] Source #

The criteria values for the segment dimension. Endpoints with matching attribute values are included or excluded from the segment, depending on the setting for Type.

sdDimensionType :: Lens' SetDimension (Maybe DimensionType) Source #

The type of dimension: INCLUSIVE - Endpoints that match the criteria are included in the segment. EXCLUSIVE - Endpoints that match the criteria are excluded from the segment.

TreatmentResource

data TreatmentResource Source #

Treatment resource

See: treatmentResource smart constructor.

Instances

Eq TreatmentResource Source # 
Data TreatmentResource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TreatmentResource -> c TreatmentResource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TreatmentResource #

toConstr :: TreatmentResource -> Constr #

dataTypeOf :: TreatmentResource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TreatmentResource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TreatmentResource) #

gmapT :: (forall b. Data b => b -> b) -> TreatmentResource -> TreatmentResource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TreatmentResource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TreatmentResource -> r #

gmapQ :: (forall d. Data d => d -> u) -> TreatmentResource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TreatmentResource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TreatmentResource -> m TreatmentResource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TreatmentResource -> m TreatmentResource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TreatmentResource -> m TreatmentResource #

Read TreatmentResource Source # 
Show TreatmentResource Source # 
Generic TreatmentResource Source # 
Hashable TreatmentResource Source # 
FromJSON TreatmentResource Source # 
NFData TreatmentResource Source # 

Methods

rnf :: TreatmentResource -> () #

type Rep TreatmentResource Source # 

treatmentResource :: TreatmentResource Source #

Creates a value of TreatmentResource with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

trTreatmentName :: Lens' TreatmentResource (Maybe Text) Source #

The custom name of a variation of the campaign used for A/B testing.

trSizePercent :: Lens' TreatmentResource (Maybe Int) Source #

The allocated percentage of users for this treatment.

trTreatmentDescription :: Lens' TreatmentResource (Maybe Text) Source #

A custom description for the treatment.

trId :: Lens' TreatmentResource (Maybe Text) Source #

The unique treatment ID.

WriteApplicationSettingsRequest

data WriteApplicationSettingsRequest Source #

Creating application setting request

See: writeApplicationSettingsRequest smart constructor.

Instances

Eq WriteApplicationSettingsRequest Source # 
Data WriteApplicationSettingsRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WriteApplicationSettingsRequest -> c WriteApplicationSettingsRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WriteApplicationSettingsRequest #

toConstr :: WriteApplicationSettingsRequest -> Constr #

dataTypeOf :: WriteApplicationSettingsRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WriteApplicationSettingsRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WriteApplicationSettingsRequest) #

gmapT :: (forall b. Data b => b -> b) -> WriteApplicationSettingsRequest -> WriteApplicationSettingsRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WriteApplicationSettingsRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WriteApplicationSettingsRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> WriteApplicationSettingsRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WriteApplicationSettingsRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WriteApplicationSettingsRequest -> m WriteApplicationSettingsRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteApplicationSettingsRequest -> m WriteApplicationSettingsRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteApplicationSettingsRequest -> m WriteApplicationSettingsRequest #

Read WriteApplicationSettingsRequest Source # 
Show WriteApplicationSettingsRequest Source # 
Generic WriteApplicationSettingsRequest Source # 
Hashable WriteApplicationSettingsRequest Source # 
ToJSON WriteApplicationSettingsRequest Source # 
NFData WriteApplicationSettingsRequest Source # 
type Rep WriteApplicationSettingsRequest Source # 
type Rep WriteApplicationSettingsRequest = D1 (MetaData "WriteApplicationSettingsRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "WriteApplicationSettingsRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_wasrLimits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CampaignLimits))) (S1 (MetaSel (Just Symbol "_wasrQuietTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe QuietTime)))))

writeApplicationSettingsRequest :: WriteApplicationSettingsRequest Source #

Creates a value of WriteApplicationSettingsRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • wasrLimits - The default campaign limits for the app. These limits apply to each campaign for the app, unless the campaign overrides the default with limits of its own.
  • wasrQuietTime - The default quiet time for the app. Each campaign for this app sends no messages during this time unless the campaign overrides the default with a quiet time of its own.

wasrLimits :: Lens' WriteApplicationSettingsRequest (Maybe CampaignLimits) Source #

The default campaign limits for the app. These limits apply to each campaign for the app, unless the campaign overrides the default with limits of its own.

wasrQuietTime :: Lens' WriteApplicationSettingsRequest (Maybe QuietTime) Source #

The default quiet time for the app. Each campaign for this app sends no messages during this time unless the campaign overrides the default with a quiet time of its own.

WriteCampaignRequest

data WriteCampaignRequest Source #

Used to create a campaign.

See: writeCampaignRequest smart constructor.

Instances

Eq WriteCampaignRequest Source # 
Data WriteCampaignRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WriteCampaignRequest -> c WriteCampaignRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WriteCampaignRequest #

toConstr :: WriteCampaignRequest -> Constr #

dataTypeOf :: WriteCampaignRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WriteCampaignRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WriteCampaignRequest) #

gmapT :: (forall b. Data b => b -> b) -> WriteCampaignRequest -> WriteCampaignRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WriteCampaignRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WriteCampaignRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> WriteCampaignRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WriteCampaignRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WriteCampaignRequest -> m WriteCampaignRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteCampaignRequest -> m WriteCampaignRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteCampaignRequest -> m WriteCampaignRequest #

Read WriteCampaignRequest Source # 
Show WriteCampaignRequest Source # 
Generic WriteCampaignRequest Source # 
Hashable WriteCampaignRequest Source # 
ToJSON WriteCampaignRequest Source # 
NFData WriteCampaignRequest Source # 

Methods

rnf :: WriteCampaignRequest -> () #

type Rep WriteCampaignRequest Source # 
type Rep WriteCampaignRequest = D1 (MetaData "WriteCampaignRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "WriteCampaignRequest'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_wcrSchedule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Schedule))) ((:*:) (S1 (MetaSel (Just Symbol "_wcrTreatmentName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_wcrLimits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CampaignLimits))))) ((:*:) (S1 (MetaSel (Just Symbol "_wcrIsPaused") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_wcrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_wcrHoldoutPercent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_wcrTreatmentDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_wcrMessageConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MessageConfiguration))) (S1 (MetaSel (Just Symbol "_wcrDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_wcrSegmentId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_wcrAdditionalTreatments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [WriteTreatmentResource]))) (S1 (MetaSel (Just Symbol "_wcrSegmentVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))))))

writeCampaignRequest :: WriteCampaignRequest Source #

Creates a value of WriteCampaignRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

wcrTreatmentName :: Lens' WriteCampaignRequest (Maybe Text) Source #

The custom name of a variation of the campaign used for A/B testing.

wcrLimits :: Lens' WriteCampaignRequest (Maybe CampaignLimits) Source #

The campaign limits settings.

wcrIsPaused :: Lens' WriteCampaignRequest (Maybe Bool) Source #

Indicates whether the campaign is paused. A paused campaign does not send messages unless you resume it by setting IsPaused to false.

wcrName :: Lens' WriteCampaignRequest (Maybe Text) Source #

The custom name of the campaign.

wcrHoldoutPercent :: Lens' WriteCampaignRequest (Maybe Int) Source #

The allocated percentage of end users who will not receive messages from this campaign.

wcrTreatmentDescription :: Lens' WriteCampaignRequest (Maybe Text) Source #

A custom description for the treatment.

wcrDescription :: Lens' WriteCampaignRequest (Maybe Text) Source #

A description of the campaign.

wcrSegmentId :: Lens' WriteCampaignRequest (Maybe Text) Source #

The ID of the segment to which the campaign sends messages.

wcrAdditionalTreatments :: Lens' WriteCampaignRequest [WriteTreatmentResource] Source #

Treatments that are defined in addition to the default treatment.

wcrSegmentVersion :: Lens' WriteCampaignRequest (Maybe Int) Source #

The version of the segment to which the campaign sends messages.

WriteEventStream

data WriteEventStream Source #

Request to save an EventStream.

See: writeEventStream smart constructor.

Instances

Eq WriteEventStream Source # 
Data WriteEventStream Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WriteEventStream -> c WriteEventStream #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WriteEventStream #

toConstr :: WriteEventStream -> Constr #

dataTypeOf :: WriteEventStream -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WriteEventStream) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WriteEventStream) #

gmapT :: (forall b. Data b => b -> b) -> WriteEventStream -> WriteEventStream #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WriteEventStream -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WriteEventStream -> r #

gmapQ :: (forall d. Data d => d -> u) -> WriteEventStream -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WriteEventStream -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WriteEventStream -> m WriteEventStream #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteEventStream -> m WriteEventStream #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteEventStream -> m WriteEventStream #

Read WriteEventStream Source # 
Show WriteEventStream Source # 
Generic WriteEventStream Source # 
Hashable WriteEventStream Source # 
ToJSON WriteEventStream Source # 
NFData WriteEventStream Source # 

Methods

rnf :: WriteEventStream -> () #

type Rep WriteEventStream Source # 
type Rep WriteEventStream = D1 (MetaData "WriteEventStream" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "WriteEventStream'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_wesDestinationStreamARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_wesRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

writeEventStream :: WriteEventStream Source #

Creates a value of WriteEventStream with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • wesDestinationStreamARN - The Amazon Resource Name (ARN) of the Amazon Kinesis stream or Firehose delivery stream to which you want to publish events. Firehose ARN: arn:aws:firehose:REGION:ACCOUNT_ID:deliverystreamSTREAM_NAME Kinesis ARN: arn:aws:kinesis:REGION:ACCOUNT_ID:streamSTREAM_NAME
  • wesRoleARN - The IAM role that authorizes Amazon Pinpoint to publish events to the stream in your account.

wesDestinationStreamARN :: Lens' WriteEventStream (Maybe Text) Source #

The Amazon Resource Name (ARN) of the Amazon Kinesis stream or Firehose delivery stream to which you want to publish events. Firehose ARN: arn:aws:firehose:REGION:ACCOUNT_ID:deliverystreamSTREAM_NAME Kinesis ARN: arn:aws:kinesis:REGION:ACCOUNT_ID:streamSTREAM_NAME

wesRoleARN :: Lens' WriteEventStream (Maybe Text) Source #

The IAM role that authorizes Amazon Pinpoint to publish events to the stream in your account.

WriteSegmentRequest

data WriteSegmentRequest Source #

Segment definition.

See: writeSegmentRequest smart constructor.

Instances

Eq WriteSegmentRequest Source # 
Data WriteSegmentRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WriteSegmentRequest -> c WriteSegmentRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WriteSegmentRequest #

toConstr :: WriteSegmentRequest -> Constr #

dataTypeOf :: WriteSegmentRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WriteSegmentRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WriteSegmentRequest) #

gmapT :: (forall b. Data b => b -> b) -> WriteSegmentRequest -> WriteSegmentRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WriteSegmentRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WriteSegmentRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> WriteSegmentRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WriteSegmentRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WriteSegmentRequest -> m WriteSegmentRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteSegmentRequest -> m WriteSegmentRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteSegmentRequest -> m WriteSegmentRequest #

Read WriteSegmentRequest Source # 
Show WriteSegmentRequest Source # 
Generic WriteSegmentRequest Source # 
Hashable WriteSegmentRequest Source # 
ToJSON WriteSegmentRequest Source # 
NFData WriteSegmentRequest Source # 

Methods

rnf :: WriteSegmentRequest -> () #

type Rep WriteSegmentRequest Source # 
type Rep WriteSegmentRequest = D1 (MetaData "WriteSegmentRequest" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "WriteSegmentRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_wsrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_wsrDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SegmentDimensions)))))

writeSegmentRequest :: WriteSegmentRequest Source #

Creates a value of WriteSegmentRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

wsrDimensions :: Lens' WriteSegmentRequest (Maybe SegmentDimensions) Source #

The segment dimensions attributes.

WriteTreatmentResource

data WriteTreatmentResource Source #

Used to create a campaign treatment.

See: writeTreatmentResource smart constructor.

Instances

Eq WriteTreatmentResource Source # 
Data WriteTreatmentResource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WriteTreatmentResource -> c WriteTreatmentResource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WriteTreatmentResource #

toConstr :: WriteTreatmentResource -> Constr #

dataTypeOf :: WriteTreatmentResource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WriteTreatmentResource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WriteTreatmentResource) #

gmapT :: (forall b. Data b => b -> b) -> WriteTreatmentResource -> WriteTreatmentResource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WriteTreatmentResource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WriteTreatmentResource -> r #

gmapQ :: (forall d. Data d => d -> u) -> WriteTreatmentResource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WriteTreatmentResource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WriteTreatmentResource -> m WriteTreatmentResource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteTreatmentResource -> m WriteTreatmentResource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteTreatmentResource -> m WriteTreatmentResource #

Read WriteTreatmentResource Source # 
Show WriteTreatmentResource Source # 
Generic WriteTreatmentResource Source # 
Hashable WriteTreatmentResource Source # 
ToJSON WriteTreatmentResource Source # 
NFData WriteTreatmentResource Source # 

Methods

rnf :: WriteTreatmentResource -> () #

type Rep WriteTreatmentResource Source # 
type Rep WriteTreatmentResource = D1 (MetaData "WriteTreatmentResource" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.5.0-JLpgkZ2NlnfGDtlP1u3vKU" False) (C1 (MetaCons "WriteTreatmentResource'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_wtrSchedule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Schedule))) (S1 (MetaSel (Just Symbol "_wtrTreatmentName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_wtrSizePercent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) ((:*:) (S1 (MetaSel (Just Symbol "_wtrTreatmentDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_wtrMessageConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MessageConfiguration)))))))

writeTreatmentResource :: WriteTreatmentResource Source #

Creates a value of WriteTreatmentResource with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

wtrTreatmentName :: Lens' WriteTreatmentResource (Maybe Text) Source #

The custom name of a variation of the campaign used for A/B testing.

wtrSizePercent :: Lens' WriteTreatmentResource (Maybe Int) Source #

The allocated percentage of users for this treatment.

wtrTreatmentDescription :: Lens' WriteTreatmentResource (Maybe Text) Source #

A custom description for the treatment.