amazonka-pinpoint-1.4.5: Amazon Pinpoint SDK.

Copyright(c) 2013-2016 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay@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

_ForbiddenException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Prism for ForbiddenException' errors.

NotFoundException

_NotFoundException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Prism for NotFoundException' errors.

TooManyRequestsException

_TooManyRequestsException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Prism for TooManyRequestsException' errors.

InternalServerErrorException

_InternalServerErrorException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Prism for InternalServerErrorException' errors.

MethodNotAllowedException

_MethodNotAllowedException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Prism for MethodNotAllowedException' errors.

BadRequestException

_BadRequestException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Prism for BadRequestException' errors.

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

GetImportJob

GetSegmentVersions

DeleteCampaign

UpdateCampaign

GetSegmentVersion

CreateSegment

UpdateEndpoint

CreateCampaign

GetEndpoint

GetSegment

UpdateEndpointsBatch

GetCampaign

UpdateGCMChannel

DeleteGCMChannel

GetCampaignActivities

DeleteAPNSChannel

UpdateAPNSChannel

GetCampaignVersions

GetAPNSChannel

GetImportJobs

GetCampaignVersion

DeleteSegment

UpdateSegment

GetCampaigns

UpdateApplicationSettings

GetSegments

CreateImportJob

GetApplicationSettings

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 #

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

Methods

rnf :: Action -> () #

ToHeader Action Source # 

Methods

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

ToQuery Action Source # 
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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 # 
ToJSON AttributeType Source # 
FromJSON AttributeType Source # 
NFData AttributeType Source # 

Methods

rnf :: AttributeType -> () #

ToHeader AttributeType Source # 
ToQuery 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 -> () #

ToHeader CampaignStatus Source # 
ToQuery 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

Constructors

APNS 
GCM 

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 # 
ToJSON ChannelType Source # 
FromJSON ChannelType Source # 
NFData ChannelType Source # 

Methods

rnf :: ChannelType -> () #

ToHeader ChannelType Source # 
ToQuery 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.4.5-HRFryQyBdxcJKvn2qKzTo3" False) ((:+:) (C1 (MetaCons "APNS" PrefixI False) U1) (C1 (MetaCons "GCM" 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 # 
ToJSON DefinitionFormat Source # 
FromJSON DefinitionFormat Source # 
NFData DefinitionFormat Source # 

Methods

rnf :: DefinitionFormat -> () #

ToHeader DefinitionFormat Source # 
ToQuery 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.4.5-HRFryQyBdxcJKvn2qKzTo3" False) ((:+:) (C1 (MetaCons "CSV" PrefixI False) U1) (C1 (MetaCons "JSON" 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 # 
ToJSON DimensionType Source # 
FromJSON DimensionType Source # 
NFData DimensionType Source # 

Methods

rnf :: DimensionType -> () #

ToHeader DimensionType Source # 
ToQuery 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

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

Methods

rnf :: Duration -> () #

ToHeader Duration Source # 

Methods

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

ToQuery Duration Source # 
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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 # 
ToJSON Frequency Source # 
FromJSON Frequency Source # 
NFData Frequency Source # 

Methods

rnf :: Frequency -> () #

ToHeader Frequency Source # 
ToQuery 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 -> () #

ToHeader JobStatus Source # 
ToQuery 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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))))

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 # 
ToJSON RecencyType Source # 
FromJSON RecencyType Source # 
NFData RecencyType Source # 

Methods

rnf :: RecencyType -> () #

ToHeader RecencyType Source # 
ToQuery 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 -> () #

ToHeader SegmentType Source # 
ToQuery 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.4.5-HRFryQyBdxcJKvn2qKzTo3" False) ((:+:) (C1 (MetaCons "Dimensional" PrefixI False) U1) (C1 (MetaCons "Import" PrefixI False) U1))

APNSChannelRequest

data APNSChannelRequest Source #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" False) (C1 (MetaCons "APNSChannelRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_acrPrivateKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_acrCertificate") 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:

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

The certificate private key.

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

The distribution certificate from Apple.

APNSChannelResponse

data APNSChannelResponse Source #

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 # 

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.

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

Is this channel archived

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

Undocumented member.

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

When was this segment created

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

Who last updated this entry

ActivitiesResponse

data ActivitiesResponse Source #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 "_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.
  • 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.

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.

ApplicationSettingsResource

data ApplicationSettingsResource Source #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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.

AttributeDimension

data AttributeDimension Source #

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 # 
ToJSON AttributeDimension Source # 
FromJSON 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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.

CampaignLimits

data CampaignLimits Source #

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 # 
ToJSON CampaignLimits Source # 
FromJSON 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.4.5-HRFryQyBdxcJKvn2qKzTo3" False) (C1 (MetaCons "CampaignLimits'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_clDaily") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_clTotal") 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:

  • clDaily - The maximum number of messages that the campaign can send daily.
  • clTotal - The maximum total number of messages that the campaign can send.

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.

CampaignResponse

data CampaignResponse Source #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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.

CampaignState

data CampaignState Source #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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.

EndpointBatchItem

data EndpointBatchItem Source #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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.
  • 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 receives all messages. NONE – User receives no messages.
  • ebiId - Undocumented member.
  • ebiChannelType - The channel type. Valid values: APNS, GCM

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.

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 receives all messages. NONE – User receives no messages.

ebiId :: Lens' EndpointBatchItem (Maybe Text) Source #

Undocumented member.

ebiChannelType :: Lens' EndpointBatchItem (Maybe ChannelType) Source #

The channel type. Valid values: APNS, GCM

EndpointBatchRequest

data EndpointBatchRequest Source #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

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 # 
ToJSON EndpointDemographic Source # 
FromJSON 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 #

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 # 
ToJSON EndpointLocation Source # 
FromJSON 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).

EndpointRequest

data EndpointRequest Source #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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.
  • 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 receives all messages. NONE – User receives no messages.
  • erChannelType - The channel type. Valid values: APNS, GCM

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.

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 receives all messages. NONE – User receives no messages.

erChannelType :: Lens' EndpointRequest (Maybe ChannelType) Source #

The channel type. Valid values: APNS, GCM

EndpointResponse

data EndpointResponse Source #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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))) (S1 (MetaSel (Just Symbol "_eShardId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

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.
  • 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 receives all messages. NONE – User receives no 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: APNS, GCM
  • eShardId - The ShardId of endpoint

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.

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 receives all messages. NONE – User receives no 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: APNS, GCM

eShardId :: Lens' EndpointResponse (Maybe Text) Source #

The ShardId of endpoint

EndpointUser

data EndpointUser Source #

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 # 
ToJSON EndpointUser Source # 
FromJSON 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 attributesd specific to the user.

euUserId :: Lens' EndpointUser (Maybe Text) Source #

The unique ID of the user.

GCMChannelRequest

data GCMChannelRequest Source #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" True) (C1 (MetaCons "GCMChannelRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_gcrAPIKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

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.

gcrAPIKey :: Lens' GCMChannelRequest (Maybe Text) Source #

Platform credential API key from Google.

GCMChannelResponse

data GCMChannelResponse Source #

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 # 

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

gcCredential :: Lens' GCMChannelResponse (Maybe Text) Source #

The GCM API key from Google.

gcIsArchived :: Lens' GCMChannelResponse (Maybe Bool) Source #

Is this channel archived

gcId :: Lens' GCMChannelResponse (Maybe Text) Source #

Undocumented member.

gcCreationDate :: Lens' GCMChannelResponse (Maybe Text) Source #

When was this segment created

gcLastModifiedBy :: Lens' GCMChannelResponse (Maybe Text) Source #

Who last updated this entry

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

ToJSON Message Source # 
FromJSON 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.
  • mBody - The message body. Can include up to 140 characters.
  • 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.

mBody :: Lens' Message (Maybe Text) Source #

The message body. Can include up to 140 characters.

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 #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

Undocumented member.

mbMessage :: Lens' MessageBody (Maybe Text) Source #

Undocumented member.

MessageConfiguration

data MessageConfiguration Source #

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 # 
ToJSON MessageConfiguration Source # 
FromJSON MessageConfiguration Source # 
NFData MessageConfiguration Source # 

Methods

rnf :: MessageConfiguration -> () #

type Rep MessageConfiguration Source # 
type Rep MessageConfiguration = D1 (MetaData "MessageConfiguration" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.4.5-HRFryQyBdxcJKvn2qKzTo3" False) (C1 (MetaCons "MessageConfiguration'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_mcAPNSMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Message))) ((:*:) (S1 (MetaSel (Just Symbol "_mcGCMMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Message))) (S1 (MetaSel (Just Symbol "_mcDefaultMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Message))))))

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.

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.

QuietTime

data QuietTime Source #

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 # 
ToJSON QuietTime Source # 
FromJSON 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

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 # 
ToJSON RecencyDimension Source # 
FromJSON 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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

Schedule

data Schedule Source #

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 #

ToJSON Schedule Source # 
FromJSON 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 #

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 # 
ToJSON SegmentBehaviors Source # 
FromJSON 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

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 # 
ToJSON SegmentDemographics Source # 
FromJSON 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.
  • 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.

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 #

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 # 
ToJSON SegmentDimensions Source # 
FromJSON SegmentDimensions Source # 
NFData SegmentDimensions Source # 

Methods

rnf :: SegmentDimensions -> () #

type Rep SegmentDimensions Source # 
type Rep SegmentDimensions = D1 (MetaData "SegmentDimensions" "Network.AWS.Pinpoint.Types.Product" "amazonka-pinpoint-1.4.5-HRFryQyBdxcJKvn2qKzTo3" False) (C1 (MetaCons "SegmentDimensions'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sdLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SegmentLocation))) (S1 (MetaSel (Just Symbol "_sdDemographic") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SegmentDemographics)))) ((:*:) (S1 (MetaSel (Just Symbol "_sdBehavior") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SegmentBehaviors))) (S1 (MetaSel (Just Symbol "_sdAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text AttributeDimension)))))))

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 #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 "_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
  • 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 #

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 # 
ToJSON SegmentLocation Source # 
FromJSON 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

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 #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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.

SetDimension

data SetDimension Source #

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 # 
ToJSON SetDimension Source # 
FromJSON 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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

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 #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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.

WriteSegmentRequest

data WriteSegmentRequest Source #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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 #

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.4.5-HRFryQyBdxcJKvn2qKzTo3" 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.