gogol-affiliates-0.3.0: Google Affiliate Network SDK.

Copyright(c) 2015-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.Google.Affiliates.Types

Contents

Description

 

Synopsis

Service Configuration

affiliatesService :: ServiceConfig Source #

Default request referring to version v1beta1 of the Google Affiliate Network API. This contains the host and root path used as a starting point for constructing service requests.

Event

data Event Source #

An EventResource.

See: event smart constructor.

Instances

Eq Event Source # 

Methods

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

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

Data Event Source # 

Methods

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

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

toConstr :: Event -> Constr #

dataTypeOf :: Event -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Event Source # 

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 

Associated Types

type Rep Event :: * -> * #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

ToJSON Event Source # 
FromJSON Event Source # 
type Rep Event Source # 
type Rep Event = D1 (MetaData "Event" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "Event'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_eModifyDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_eStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_eCommissionableSales") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Money))) (S1 (MetaSel (Just Symbol "_eChargeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_eAdvertiserName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_eChargeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_eMemberId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_eKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_eNetworkFee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Money))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_eAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_eEventDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')))) ((:*:) (S1 (MetaSel (Just Symbol "_eProducts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [EventProductsItem]))) (S1 (MetaSel (Just Symbol "_ePublisherFee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Money))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_eType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_eOrderId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ePublisherId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_eEarnings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Money))) (S1 (MetaSel (Just Symbol "_ePublisherName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))))

event :: Event Source #

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

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

eModifyDate :: Lens' Event (Maybe UTCTime) Source #

The date-time this event was last modified as a RFC 3339 date-time value.

eStatus :: Lens' Event (Maybe Text) Source #

Status of the event (active|canceled). Only returned for charge and conversion events.

eCommissionableSales :: Lens' Event (Maybe Money) Source #

Amount of money exchanged during the transaction. Only returned for charge and conversion events.

eChargeId :: Lens' Event (Maybe Text) Source #

The charge ID for this event. Only returned for charge events.

eAdvertiserName :: Lens' Event (Maybe Text) Source #

The name of the advertiser for this event.

eChargeType :: Lens' Event (Maybe Text) Source #

Charge type of the event (other|slotting_fee|monthly_minimum|tier_bonus|debit|credit). Only returned for charge events.

eMemberId :: Lens' Event (Maybe Text) Source #

The ID of the member attached to this event. Only returned for conversion events.

eKind :: Lens' Event Text Source #

The kind for one event.

eNetworkFee :: Lens' Event (Maybe Money) Source #

Fee that the advertiser paid to the Google Affiliate Network.

eAdvertiserId :: Lens' Event (Maybe Int64) Source #

The ID of advertiser for this event.

eEventDate :: Lens' Event (Maybe UTCTime) Source #

The date-time this event was initiated as a RFC 3339 date-time value.

eProducts :: Lens' Event [EventProductsItem] Source #

Products associated with the event.

ePublisherFee :: Lens' Event (Maybe Money) Source #

Fee that the advertiser paid to the publisher.

eType :: Lens' Event (Maybe Text) Source #

Type of the event (action|transaction|charge).

eOrderId :: Lens' Event (Maybe Text) Source #

The order ID for this event. Only returned for conversion events.

ePublisherId :: Lens' Event (Maybe Int64) Source #

The ID of the publisher for this event.

eEarnings :: Lens' Event (Maybe Money) Source #

Earnings by the publisher.

ePublisherName :: Lens' Event (Maybe Text) Source #

The name of the publisher for this event.

PublishersGetRole

data PublishersGetRole Source #

The role of the requester. Valid values: 'advertisers' or 'publishers'.

Constructors

PGRAdvertisers

advertisers The requester is requesting as an advertiser.

PGRPublishers

publishers The requester is requesting as a publisher.

Instances

Enum PublishersGetRole Source # 
Eq PublishersGetRole Source # 
Data PublishersGetRole Source # 

Methods

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

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

toConstr :: PublishersGetRole -> Constr #

dataTypeOf :: PublishersGetRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PublishersGetRole Source # 
Read PublishersGetRole Source # 
Show PublishersGetRole Source # 
Generic PublishersGetRole Source # 
Hashable PublishersGetRole Source # 
ToJSON PublishersGetRole Source # 
FromJSON PublishersGetRole Source # 
FromHttpApiData PublishersGetRole Source # 
ToHttpApiData PublishersGetRole Source # 
type Rep PublishersGetRole Source # 
type Rep PublishersGetRole = D1 (MetaData "PublishersGetRole" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "PGRAdvertisers" PrefixI False) U1) (C1 (MetaCons "PGRPublishers" PrefixI False) U1))

ReportsGetEventType

data ReportsGetEventType Source #

Filters out all events that are not of the given type. Valid values: 'action', 'transaction', or 'charge'. Optional.

Constructors

Action

action Event type is action.

Charge

charge Event type is charge.

Transaction

transaction Event type is transaction.

Instances

Enum ReportsGetEventType Source # 
Eq ReportsGetEventType Source # 
Data ReportsGetEventType Source # 

Methods

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

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

toConstr :: ReportsGetEventType -> Constr #

dataTypeOf :: ReportsGetEventType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ReportsGetEventType Source # 
Read ReportsGetEventType Source # 
Show ReportsGetEventType Source # 
Generic ReportsGetEventType Source # 
Hashable ReportsGetEventType Source # 
ToJSON ReportsGetEventType Source # 
FromJSON ReportsGetEventType Source # 
FromHttpApiData ReportsGetEventType Source # 
ToHttpApiData ReportsGetEventType Source # 
type Rep ReportsGetEventType Source # 
type Rep ReportsGetEventType = D1 (MetaData "ReportsGetEventType" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "Action" PrefixI False) U1) ((:+:) (C1 (MetaCons "Charge" PrefixI False) U1) (C1 (MetaCons "Transaction" PrefixI False) U1)))

ReportsGetStatus

data ReportsGetStatus Source #

Filters out all events that do not have the given status. Valid values: 'active', 'canceled', or 'invalid'. Optional.

Constructors

Active

active Event is currently active.

Canceled

canceled Event is currently canceled.

Invalid

invalid Event is currently invalid.

Instances

Enum ReportsGetStatus Source # 
Eq ReportsGetStatus Source # 
Data ReportsGetStatus Source # 

Methods

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

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

toConstr :: ReportsGetStatus -> Constr #

dataTypeOf :: ReportsGetStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ReportsGetStatus Source # 
Read ReportsGetStatus Source # 
Show ReportsGetStatus Source # 
Generic ReportsGetStatus Source # 
Hashable ReportsGetStatus Source # 
ToJSON ReportsGetStatus Source # 
FromJSON ReportsGetStatus Source # 
FromHttpApiData ReportsGetStatus Source # 
ToHttpApiData ReportsGetStatus Source # 
type Rep ReportsGetStatus Source # 
type Rep ReportsGetStatus = D1 (MetaData "ReportsGetStatus" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "Active" PrefixI False) U1) ((:+:) (C1 (MetaCons "Canceled" PrefixI False) U1) (C1 (MetaCons "Invalid" PrefixI False) U1)))

LinksListPromotionType

data LinksListPromotionType Source #

The promotion type.

Constructors

Coupon
coupon
FreeGift
free_gift
FreeShipping
free_shipping
PercentOff
percent_off
PriceCut
price_cut

Instances

Enum LinksListPromotionType Source # 
Eq LinksListPromotionType Source # 
Data LinksListPromotionType Source # 

Methods

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

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

toConstr :: LinksListPromotionType -> Constr #

dataTypeOf :: LinksListPromotionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LinksListPromotionType Source # 
Read LinksListPromotionType Source # 
Show LinksListPromotionType Source # 
Generic LinksListPromotionType Source # 
Hashable LinksListPromotionType Source # 
ToJSON LinksListPromotionType Source # 
FromJSON LinksListPromotionType Source # 
FromHttpApiData LinksListPromotionType Source # 
ToHttpApiData LinksListPromotionType Source # 
type Rep LinksListPromotionType Source # 
type Rep LinksListPromotionType = D1 (MetaData "LinksListPromotionType" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) ((:+:) (C1 (MetaCons "Coupon" PrefixI False) U1) (C1 (MetaCons "FreeGift" PrefixI False) U1)) ((:+:) (C1 (MetaCons "FreeShipping" PrefixI False) U1) ((:+:) (C1 (MetaCons "PercentOff" PrefixI False) U1) (C1 (MetaCons "PriceCut" PrefixI False) U1))))

EventsListType

data EventsListType Source #

Filters out all events that are not of the given type. Valid values: 'action', 'transaction', 'charge'. Optional.

Constructors

ELTAction

action The completion of an application, sign-up, or other process. For example, an action occurs if a user clicks an ad for a credit card and completes an application for that card.

ELTCharge

charge A charge event is typically a payment between an advertiser, publisher or Google.

ELTTransaction

transaction A conversion event, typically an e-commerce transaction. Some advertisers use a transaction to record other types of events, such as magazine subscriptions.

Instances

Enum EventsListType Source # 
Eq EventsListType Source # 
Data EventsListType Source # 

Methods

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

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

toConstr :: EventsListType -> Constr #

dataTypeOf :: EventsListType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EventsListType Source # 
Read EventsListType Source # 
Show EventsListType Source # 
Generic EventsListType Source # 

Associated Types

type Rep EventsListType :: * -> * #

Hashable EventsListType Source # 
ToJSON EventsListType Source # 
FromJSON EventsListType Source # 
FromHttpApiData EventsListType Source # 
ToHttpApiData EventsListType Source # 
type Rep EventsListType Source # 
type Rep EventsListType = D1 (MetaData "EventsListType" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "ELTAction" PrefixI False) U1) ((:+:) (C1 (MetaCons "ELTCharge" PrefixI False) U1) (C1 (MetaCons "ELTTransaction" PrefixI False) U1)))

LinksListRole

data LinksListRole Source #

The role of the requester. Valid values: 'advertisers' or 'publishers'.

Constructors

LLRAdvertisers

advertisers The requester is requesting as an advertiser.

LLRPublishers

publishers The requester is requesting as a publisher.

Instances

Enum LinksListRole Source # 
Eq LinksListRole Source # 
Data LinksListRole Source # 

Methods

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

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

toConstr :: LinksListRole -> Constr #

dataTypeOf :: LinksListRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LinksListRole Source # 
Read LinksListRole Source # 
Show LinksListRole Source # 
Generic LinksListRole Source # 

Associated Types

type Rep LinksListRole :: * -> * #

Hashable LinksListRole Source # 
ToJSON LinksListRole Source # 
FromJSON LinksListRole Source # 
FromHttpApiData LinksListRole Source # 
ToHttpApiData LinksListRole Source # 
type Rep LinksListRole Source # 
type Rep LinksListRole = D1 (MetaData "LinksListRole" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "LLRAdvertisers" PrefixI False) U1) (C1 (MetaCons "LLRPublishers" PrefixI False) U1))

ReportsGetReportType

data ReportsGetReportType Source #

The type of report being requested. Valid values: 'order_delta'. Required.

Constructors

OrderDelta

order_delta The order delta report type.

Instances

Enum ReportsGetReportType Source # 
Eq ReportsGetReportType Source # 
Data ReportsGetReportType Source # 

Methods

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

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

toConstr :: ReportsGetReportType -> Constr #

dataTypeOf :: ReportsGetReportType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ReportsGetReportType Source # 
Read ReportsGetReportType Source # 
Show ReportsGetReportType Source # 
Generic ReportsGetReportType Source # 
Hashable ReportsGetReportType Source # 
ToJSON ReportsGetReportType Source # 
FromJSON ReportsGetReportType Source # 
FromHttpApiData ReportsGetReportType Source # 
ToHttpApiData ReportsGetReportType Source # 
type Rep ReportsGetReportType Source # 
type Rep ReportsGetReportType = D1 (MetaData "ReportsGetReportType" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "OrderDelta" PrefixI False) U1)

AdvertisersListRole

data AdvertisersListRole Source #

The role of the requester. Valid values: 'advertisers' or 'publishers'.

Constructors

ALRAdvertisers

advertisers The requester is requesting as an advertiser.

ALRPublishers

publishers The requester is requesting as a publisher.

Instances

Enum AdvertisersListRole Source # 
Eq AdvertisersListRole Source # 
Data AdvertisersListRole Source # 

Methods

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

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

toConstr :: AdvertisersListRole -> Constr #

dataTypeOf :: AdvertisersListRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AdvertisersListRole Source # 
Read AdvertisersListRole Source # 
Show AdvertisersListRole Source # 
Generic AdvertisersListRole Source # 
Hashable AdvertisersListRole Source # 
ToJSON AdvertisersListRole Source # 
FromJSON AdvertisersListRole Source # 
FromHttpApiData AdvertisersListRole Source # 
ToHttpApiData AdvertisersListRole Source # 
type Rep AdvertisersListRole Source # 
type Rep AdvertisersListRole = D1 (MetaData "AdvertisersListRole" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "ALRAdvertisers" PrefixI False) U1) (C1 (MetaCons "ALRPublishers" PrefixI False) U1))

Money

data Money Source #

An ApiMoneyProto.

See: money smart constructor.

Instances

Eq Money Source # 

Methods

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

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

Data Money Source # 

Methods

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

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

toConstr :: Money -> Constr #

dataTypeOf :: Money -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Money Source # 

Methods

showsPrec :: Int -> Money -> ShowS #

show :: Money -> String #

showList :: [Money] -> ShowS #

Generic Money Source # 

Associated Types

type Rep Money :: * -> * #

Methods

from :: Money -> Rep Money x #

to :: Rep Money x -> Money #

ToJSON Money Source # 
FromJSON Money Source # 
type Rep Money Source # 
type Rep Money = D1 (MetaData "Money" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "Money'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_mAmount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_mCurrencyCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

money :: Money Source #

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

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

mAmount :: Lens' Money (Maybe Double) Source #

The amount of money.

mCurrencyCode :: Lens' Money (Maybe Text) Source #

The 3-letter code of the currency in question.

Link

data Link Source #

A LinkResource.

See: link smart constructor.

lDestinationURL :: Lens' Link (Maybe Text) Source #

The destination URL for the link.

lClickTrackingURL :: Lens' Link (Maybe Text) Source #

Tracking url for clicks.

lCreateDate :: Lens' Link (Maybe UTCTime) Source #

Date that this link was created.

lKind :: Lens' Link Text Source #

The kind for one entity.

lAdvertiserId :: Lens' Link (Maybe Int64) Source #

The advertiser id for the advertiser who owns this link.

lEndDate :: Lens' Link (Maybe UTCTime) Source #

Date that this link becomes inactive.

lImageAltText :: Lens' Link (Maybe Text) Source #

image alt text.

lStartDate :: Lens' Link (Maybe UTCTime) Source #

Date that this link becomes active.

lName :: Lens' Link (Maybe Text) Source #

The logical name for this link.

lImpressionTrackingURL :: Lens' Link (Maybe Text) Source #

Tracking url for impressions.

lSpecialOffers :: Lens' Link (Maybe LinkSpecialOffers) Source #

Special offers on the link.

lEpcSevenDayAverage :: Lens' Link (Maybe Money) Source #

The sum of fees paid to publishers divided by the total number of clicks over the past seven days on this link. This value should be multiplied by 100 at the time of display.

lId :: Lens' Link (Maybe Int64) Source #

The ID of this link.

lEpcNinetyDayAverage :: Lens' Link (Maybe Money) Source #

The sum of fees paid to publishers divided by the total number of clicks over the past three months on this link. This value should be multiplied by 100 at the time of display.

lLinkType :: Lens' Link (Maybe Text) Source #

The link type.

lIsActive :: Lens' Link (Maybe Bool) Source #

Flag for if this link is active.

LinksInsertRole

data LinksInsertRole Source #

The role of the requester. Valid values: 'advertisers' or 'publishers'.

Constructors

LIRAdvertisers

advertisers The requester is requesting as an advertiser.

LIRPublishers

publishers The requester is requesting as a publisher.

Instances

Enum LinksInsertRole Source # 
Eq LinksInsertRole Source # 
Data LinksInsertRole Source # 

Methods

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

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

toConstr :: LinksInsertRole -> Constr #

dataTypeOf :: LinksInsertRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LinksInsertRole Source # 
Read LinksInsertRole Source # 
Show LinksInsertRole Source # 
Generic LinksInsertRole Source # 
Hashable LinksInsertRole Source # 
ToJSON LinksInsertRole Source # 
FromJSON LinksInsertRole Source # 
FromHttpApiData LinksInsertRole Source # 
ToHttpApiData LinksInsertRole Source # 
type Rep LinksInsertRole Source # 
type Rep LinksInsertRole = D1 (MetaData "LinksInsertRole" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "LIRAdvertisers" PrefixI False) U1) (C1 (MetaCons "LIRPublishers" PrefixI False) U1))

CcOffers

data CcOffers Source #

Instances

Eq CcOffers Source # 
Data CcOffers Source # 

Methods

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

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

toConstr :: CcOffers -> Constr #

dataTypeOf :: CcOffers -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CcOffers Source # 
Generic CcOffers Source # 

Associated Types

type Rep CcOffers :: * -> * #

Methods

from :: CcOffers -> Rep CcOffers x #

to :: Rep CcOffers x -> CcOffers #

ToJSON CcOffers Source # 
FromJSON CcOffers Source # 
type Rep CcOffers Source # 
type Rep CcOffers = D1 (MetaData "CcOffers" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "CcOffers'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_coKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_coItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CcOffer])))))

ccOffers :: CcOffers Source #

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

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

coKind :: Lens' CcOffers Text Source #

The kind for a page of credit card offers.

coItems :: Lens' CcOffers [CcOffer] Source #

The credit card offers.

PublishersListRole

data PublishersListRole Source #

The role of the requester. Valid values: 'advertisers' or 'publishers'.

Constructors

PLRAdvertisers

advertisers The requester is requesting as an advertiser.

PLRPublishers

publishers The requester is requesting as a publisher.

Instances

Enum PublishersListRole Source # 
Eq PublishersListRole Source # 
Data PublishersListRole Source # 

Methods

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

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

toConstr :: PublishersListRole -> Constr #

dataTypeOf :: PublishersListRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PublishersListRole Source # 
Read PublishersListRole Source # 
Show PublishersListRole Source # 
Generic PublishersListRole Source # 
Hashable PublishersListRole Source # 
ToJSON PublishersListRole Source # 
FromJSON PublishersListRole Source # 
FromHttpApiData PublishersListRole Source # 
ToHttpApiData PublishersListRole Source # 
type Rep PublishersListRole Source # 
type Rep PublishersListRole = D1 (MetaData "PublishersListRole" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "PLRAdvertisers" PrefixI False) U1) (C1 (MetaCons "PLRPublishers" PrefixI False) U1))

CcOfferDefaultFeesItem

data CcOfferDefaultFeesItem Source #

Instances

Eq CcOfferDefaultFeesItem Source # 
Data CcOfferDefaultFeesItem Source # 

Methods

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

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

toConstr :: CcOfferDefaultFeesItem -> Constr #

dataTypeOf :: CcOfferDefaultFeesItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CcOfferDefaultFeesItem Source # 
Generic CcOfferDefaultFeesItem Source # 
ToJSON CcOfferDefaultFeesItem Source # 
FromJSON CcOfferDefaultFeesItem Source # 
type Rep CcOfferDefaultFeesItem Source # 
type Rep CcOfferDefaultFeesItem = D1 (MetaData "CcOfferDefaultFeesItem" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "CcOfferDefaultFeesItem'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_codfiRateType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_codfiMinRate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))) ((:*:) (S1 (MetaSel (Just Symbol "_codfiCategory") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_codfiMaxRate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))))))

ccOfferDefaultFeesItem :: CcOfferDefaultFeesItem Source #

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

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

codfiMinRate :: Lens' CcOfferDefaultFeesItem (Maybe Double) Source #

The lowest rate the issuer may charge for defaulting on debt in this category. Expressed as an absolute number, not as a percentage.

codfiCategory :: Lens' CcOfferDefaultFeesItem (Maybe Text) Source #

The type of charge, for example Purchases.

codfiMaxRate :: Lens' CcOfferDefaultFeesItem (Maybe Double) Source #

The highest rate the issuer may charge for defaulting on debt in this category. Expressed as an absolute number, not as a percentage.

Report

data Report Source #

A ReportResource representing a report of a certain type either for an advertiser or publisher.

See: report smart constructor.

Instances

Eq Report Source # 

Methods

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

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

Data Report Source # 

Methods

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

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

toConstr :: Report -> Constr #

dataTypeOf :: Report -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Report Source # 
Generic Report Source # 

Associated Types

type Rep Report :: * -> * #

Methods

from :: Report -> Rep Report x #

to :: Rep Report x -> Report #

ToJSON Report Source # 
FromJSON Report Source # 
type Rep Report Source # 

report :: Report Source #

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

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

rEndDate :: Lens' Report (Maybe Text) Source #

The end of the date range for this report, exclusive.

rTotalsRows :: Lens' Report [[JSONValue]] Source #

The totals rows for the report

rKind :: Lens' Report Text Source #

The kind for a report.

rStartDate :: Lens' Report (Maybe Text) Source #

The start of the date range for this report, inclusive.

rRows :: Lens' Report [[JSONValue]] Source #

The rows of data for the report

rMatchingRowCount :: Lens' Report (Maybe Int64) Source #

The number of matching rows before paging is applied.

rColumnNames :: Lens' Report [Text] Source #

The column names for the report

rType :: Lens' Report (Maybe Text) Source #

The report type.

LinksListAuthorship

data LinksListAuthorship Source #

The role of the author of the link.

Constructors

LLAAdvertiser
advertiser
LLAPublisher
publisher

Instances

Enum LinksListAuthorship Source # 
Eq LinksListAuthorship Source # 
Data LinksListAuthorship Source # 

Methods

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

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

toConstr :: LinksListAuthorship -> Constr #

dataTypeOf :: LinksListAuthorship -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LinksListAuthorship Source # 
Read LinksListAuthorship Source # 
Show LinksListAuthorship Source # 
Generic LinksListAuthorship Source # 
Hashable LinksListAuthorship Source # 
ToJSON LinksListAuthorship Source # 
FromJSON LinksListAuthorship Source # 
FromHttpApiData LinksListAuthorship Source # 
ToHttpApiData LinksListAuthorship Source # 
type Rep LinksListAuthorship Source # 
type Rep LinksListAuthorship = D1 (MetaData "LinksListAuthorship" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "LLAAdvertiser" PrefixI False) U1) (C1 (MetaCons "LLAPublisher" PrefixI False) U1))

Advertisers

data Advertisers Source #

Instances

Eq Advertisers Source # 
Data Advertisers Source # 

Methods

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

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

toConstr :: Advertisers -> Constr #

dataTypeOf :: Advertisers -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Advertisers Source # 
Generic Advertisers Source # 

Associated Types

type Rep Advertisers :: * -> * #

ToJSON Advertisers Source # 
FromJSON Advertisers Source # 
type Rep Advertisers Source # 
type Rep Advertisers = D1 (MetaData "Advertisers" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "Advertisers'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_aNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_aKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_aItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Advertiser]))))))

advertisers :: Advertisers Source #

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

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

aNextPageToken :: Lens' Advertisers (Maybe Text) Source #

The 'pageToken' to pass to the next request to get the next page, if there are more to retrieve.

aKind :: Lens' Advertisers Text Source #

The kind for a page of advertisers.

aItems :: Lens' Advertisers [Advertiser] Source #

The advertiser list.

LinksGetRole

data LinksGetRole Source #

The role of the requester. Valid values: 'advertisers' or 'publishers'.

Constructors

LGRAdvertisers

advertisers The requester is requesting as an advertiser.

LGRPublishers

publishers The requester is requesting as a publisher.

Instances

Enum LinksGetRole Source # 
Eq LinksGetRole Source # 
Data LinksGetRole Source # 

Methods

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

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

toConstr :: LinksGetRole -> Constr #

dataTypeOf :: LinksGetRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LinksGetRole Source # 
Read LinksGetRole Source # 
Show LinksGetRole Source # 
Generic LinksGetRole Source # 

Associated Types

type Rep LinksGetRole :: * -> * #

Hashable LinksGetRole Source # 
ToJSON LinksGetRole Source # 
FromJSON LinksGetRole Source # 
FromHttpApiData LinksGetRole Source # 
ToHttpApiData LinksGetRole Source # 
type Rep LinksGetRole Source # 
type Rep LinksGetRole = D1 (MetaData "LinksGetRole" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "LGRAdvertisers" PrefixI False) U1) (C1 (MetaCons "LGRPublishers" PrefixI False) U1))

LinksListLinkType

data LinksListLinkType Source #

The type of the link.

Constructors

Banner
banner
Text
text

Instances

Enum LinksListLinkType Source # 
Eq LinksListLinkType Source # 
Data LinksListLinkType Source # 

Methods

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

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

toConstr :: LinksListLinkType -> Constr #

dataTypeOf :: LinksListLinkType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LinksListLinkType Source # 
Read LinksListLinkType Source # 
Show LinksListLinkType Source # 
Generic LinksListLinkType Source # 
Hashable LinksListLinkType Source # 
ToJSON LinksListLinkType Source # 
FromJSON LinksListLinkType Source # 
FromHttpApiData LinksListLinkType Source # 
ToHttpApiData LinksListLinkType Source # 
type Rep LinksListLinkType Source # 
type Rep LinksListLinkType = D1 (MetaData "LinksListLinkType" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "Banner" PrefixI False) U1) (C1 (MetaCons "Text" PrefixI False) U1))

EventsListRole

data EventsListRole Source #

The role of the requester. Valid values: 'advertisers' or 'publishers'.

Constructors

ELRAdvertisers

advertisers The requester is requesting as an advertiser.

ELRPublishers

publishers The requester is requesting as a publisher.

Instances

Enum EventsListRole Source # 
Eq EventsListRole Source # 
Data EventsListRole Source # 

Methods

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

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

toConstr :: EventsListRole -> Constr #

dataTypeOf :: EventsListRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EventsListRole Source # 
Read EventsListRole Source # 
Show EventsListRole Source # 
Generic EventsListRole Source # 

Associated Types

type Rep EventsListRole :: * -> * #

Hashable EventsListRole Source # 
ToJSON EventsListRole Source # 
FromJSON EventsListRole Source # 
FromHttpApiData EventsListRole Source # 
ToHttpApiData EventsListRole Source # 
type Rep EventsListRole Source # 
type Rep EventsListRole = D1 (MetaData "EventsListRole" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "ELRAdvertisers" PrefixI False) U1) (C1 (MetaCons "ELRPublishers" PrefixI False) U1))

EventProductsItem

data EventProductsItem Source #

Instances

Eq EventProductsItem Source # 
Data EventProductsItem Source # 

Methods

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

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

toConstr :: EventProductsItem -> Constr #

dataTypeOf :: EventProductsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show EventProductsItem Source # 
Generic EventProductsItem Source # 
ToJSON EventProductsItem Source # 
FromJSON EventProductsItem Source # 
type Rep EventProductsItem Source # 

eventProductsItem :: EventProductsItem Source #

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

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

epiSKUName :: Lens' EventProductsItem (Maybe Text) Source #

Sku name of this product.

epiNetworkFee :: Lens' EventProductsItem (Maybe Money) Source #

Fee that the advertiser paid to the Google Affiliate Network for this product.

epiQuantity :: Lens' EventProductsItem (Maybe Int64) Source #

Quantity of this product bought/exchanged.

epiCategoryName :: Lens' EventProductsItem (Maybe Text) Source #

Name of the category this product belongs to.

epiCategoryId :: Lens' EventProductsItem (Maybe Text) Source #

Id of the category this product belongs to.

epiSKU :: Lens' EventProductsItem (Maybe Text) Source #

Sku of this product.

epiPublisherFee :: Lens' EventProductsItem (Maybe Money) Source #

Fee that the advertiser paid to the publisehr for this product.

epiUnitPrice :: Lens' EventProductsItem (Maybe Money) Source #

Price per unit of this product.

epiEarnings :: Lens' EventProductsItem (Maybe Money) Source #

Amount earned by the publisher on this product.

AdvertisersListRelationshipStatus

data AdvertisersListRelationshipStatus Source #

Filters out all advertisers for which do not have the given relationship status with the requesting publisher.

Constructors

Approved

approved An advertiser that has approved your application.

Available

available An advertiser program that's accepting new publishers.

Deactivated

deactivated Deactivated means either the advertiser has removed you from their program, or it could also mean that you chose to remove yourself from the advertiser's program.

Declined

declined An advertiser that did not approve your application.

Pending

pending An advertiser program that you've already applied to, but they haven't yet decided to approve or decline your application.

Instances

Enum AdvertisersListRelationshipStatus Source # 
Eq AdvertisersListRelationshipStatus Source # 
Data AdvertisersListRelationshipStatus Source # 

Methods

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

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

toConstr :: AdvertisersListRelationshipStatus -> Constr #

dataTypeOf :: AdvertisersListRelationshipStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AdvertisersListRelationshipStatus Source # 
Read AdvertisersListRelationshipStatus Source # 
Show AdvertisersListRelationshipStatus Source # 
Generic AdvertisersListRelationshipStatus Source # 
Hashable AdvertisersListRelationshipStatus Source # 
ToJSON AdvertisersListRelationshipStatus Source # 
FromJSON AdvertisersListRelationshipStatus Source # 
FromHttpApiData AdvertisersListRelationshipStatus Source # 
ToHttpApiData AdvertisersListRelationshipStatus Source # 
type Rep AdvertisersListRelationshipStatus Source # 
type Rep AdvertisersListRelationshipStatus = D1 (MetaData "AdvertisersListRelationshipStatus" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) ((:+:) (C1 (MetaCons "Approved" PrefixI False) U1) (C1 (MetaCons "Available" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Deactivated" PrefixI False) U1) ((:+:) (C1 (MetaCons "Declined" PrefixI False) U1) (C1 (MetaCons "Pending" PrefixI False) U1))))

CcOffersListProjection

data CcOffersListProjection Source #

The set of fields to return.

Constructors

Full

full Include all offer fields. This is the default.

Summary

summary Include only the basic fields needed to display an offer.

Instances

Enum CcOffersListProjection Source # 
Eq CcOffersListProjection Source # 
Data CcOffersListProjection Source # 

Methods

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

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

toConstr :: CcOffersListProjection -> Constr #

dataTypeOf :: CcOffersListProjection -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CcOffersListProjection Source # 
Read CcOffersListProjection Source # 
Show CcOffersListProjection Source # 
Generic CcOffersListProjection Source # 
Hashable CcOffersListProjection Source # 
ToJSON CcOffersListProjection Source # 
FromJSON CcOffersListProjection Source # 
FromHttpApiData CcOffersListProjection Source # 
ToHttpApiData CcOffersListProjection Source # 
type Rep CcOffersListProjection Source # 
type Rep CcOffersListProjection = D1 (MetaData "CcOffersListProjection" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "Full" PrefixI False) U1) (C1 (MetaCons "Summary" PrefixI False) U1))

CcOfferBonusRewardsItem

data CcOfferBonusRewardsItem Source #

Instances

Eq CcOfferBonusRewardsItem Source # 
Data CcOfferBonusRewardsItem Source # 

Methods

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

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

toConstr :: CcOfferBonusRewardsItem -> Constr #

dataTypeOf :: CcOfferBonusRewardsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CcOfferBonusRewardsItem Source # 
Generic CcOfferBonusRewardsItem Source # 
ToJSON CcOfferBonusRewardsItem Source # 
FromJSON CcOfferBonusRewardsItem Source # 
type Rep CcOfferBonusRewardsItem Source # 
type Rep CcOfferBonusRewardsItem = D1 (MetaData "CcOfferBonusRewardsItem" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "CcOfferBonusRewardsItem'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cobriAmount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_cobriDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

ccOfferBonusRewardsItem :: CcOfferBonusRewardsItem Source #

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

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

cobriAmount :: Lens' CcOfferBonusRewardsItem (Maybe Double) Source #

How many units of reward will be granted.

cobriDetails :: Lens' CcOfferBonusRewardsItem (Maybe Text) Source #

The circumstances under which this rule applies, for example, booking a flight via Orbitz.

AdvertisersGetRole

data AdvertisersGetRole Source #

The role of the requester. Valid values: 'advertisers' or 'publishers'.

Constructors

AGRAdvertisers

advertisers The requester is requesting as an advertiser.

AGRPublishers

publishers The requester is requesting as a publisher.

Instances

Enum AdvertisersGetRole Source # 
Eq AdvertisersGetRole Source # 
Data AdvertisersGetRole Source # 

Methods

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

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

toConstr :: AdvertisersGetRole -> Constr #

dataTypeOf :: AdvertisersGetRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AdvertisersGetRole Source # 
Read AdvertisersGetRole Source # 
Show AdvertisersGetRole Source # 
Generic AdvertisersGetRole Source # 
Hashable AdvertisersGetRole Source # 
ToJSON AdvertisersGetRole Source # 
FromJSON AdvertisersGetRole Source # 
FromHttpApiData AdvertisersGetRole Source # 
ToHttpApiData AdvertisersGetRole Source # 
type Rep AdvertisersGetRole Source # 
type Rep AdvertisersGetRole = D1 (MetaData "AdvertisersGetRole" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "AGRAdvertisers" PrefixI False) U1) (C1 (MetaCons "AGRPublishers" PrefixI False) U1))

EventsListChargeType

data EventsListChargeType Source #

Filters out all charge events that are not of the given charge type. Valid values: 'other', 'slotting_fee', 'monthly_minimum', 'tier_bonus', 'credit', 'debit'. Optional.

Constructors

Credit

credit A credit increases the publisher's payout amount and decreases the advertiser's invoice amount.

Debit

debit A debit reduces the publisher's payout and increases the advertiser's invoice amount.

MonthlyMinimum

monthly_minimum A payment made to Google by an advertiser as a minimum monthly network fee.

Other

other Catch all. Default if unset

SlottingFee

slotting_fee A one time payment made from an advertiser to a publisher.

TierBonus

tier_bonus A payment from an advertiser to a publisher for the publisher maintaining a high tier level

Instances

Enum EventsListChargeType Source # 
Eq EventsListChargeType Source # 
Data EventsListChargeType Source # 

Methods

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

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

toConstr :: EventsListChargeType -> Constr #

dataTypeOf :: EventsListChargeType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EventsListChargeType Source # 
Read EventsListChargeType Source # 
Show EventsListChargeType Source # 
Generic EventsListChargeType Source # 
Hashable EventsListChargeType Source # 
ToJSON EventsListChargeType Source # 
FromJSON EventsListChargeType Source # 
FromHttpApiData EventsListChargeType Source # 
ToHttpApiData EventsListChargeType Source # 
type Rep EventsListChargeType Source # 
type Rep EventsListChargeType = D1 (MetaData "EventsListChargeType" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) ((:+:) (C1 (MetaCons "Credit" PrefixI False) U1) ((:+:) (C1 (MetaCons "Debit" PrefixI False) U1) (C1 (MetaCons "MonthlyMinimum" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Other" PrefixI False) U1) ((:+:) (C1 (MetaCons "SlottingFee" PrefixI False) U1) (C1 (MetaCons "TierBonus" PrefixI False) U1))))

PublishersListRelationshipStatus

data PublishersListRelationshipStatus Source #

Filters out all publishers for which do not have the given relationship status with the requesting publisher.

Constructors

PLRSApproved

approved Publishers you've approved to your program.

PLRSAvailable

available Publishers available for you to recruit.

PLRSDeactivated

deactivated A publisher that you terminated from your program. Publishers also have the ability to remove themselves from your program.

PLRSDeclined

declined A publisher that you did not approve to your program.

PLRSPending

pending Publishers that have applied to your program. We recommend reviewing and deciding on pending publishers on a weekly basis.

Instances

Enum PublishersListRelationshipStatus Source # 
Eq PublishersListRelationshipStatus Source # 
Data PublishersListRelationshipStatus Source # 

Methods

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

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

toConstr :: PublishersListRelationshipStatus -> Constr #

dataTypeOf :: PublishersListRelationshipStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PublishersListRelationshipStatus Source # 
Read PublishersListRelationshipStatus Source # 
Show PublishersListRelationshipStatus Source # 
Generic PublishersListRelationshipStatus Source # 
Hashable PublishersListRelationshipStatus Source # 
ToJSON PublishersListRelationshipStatus Source # 
FromJSON PublishersListRelationshipStatus Source # 
FromHttpApiData PublishersListRelationshipStatus Source # 
ToHttpApiData PublishersListRelationshipStatus Source # 
type Rep PublishersListRelationshipStatus Source # 
type Rep PublishersListRelationshipStatus = D1 (MetaData "PublishersListRelationshipStatus" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) ((:+:) (C1 (MetaCons "PLRSApproved" PrefixI False) U1) (C1 (MetaCons "PLRSAvailable" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PLRSDeactivated" PrefixI False) U1) ((:+:) (C1 (MetaCons "PLRSDeclined" PrefixI False) U1) (C1 (MetaCons "PLRSPending" PrefixI False) U1))))

ReportsGetRole

data ReportsGetRole Source #

The role of the requester. Valid values: 'advertisers' or 'publishers'.

Constructors

RGRAdvertisers

advertisers The requester is requesting as an advertiser.

RGRPublishers

publishers The requester is requesting as a publisher.

Instances

Enum ReportsGetRole Source # 
Eq ReportsGetRole Source # 
Data ReportsGetRole Source # 

Methods

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

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

toConstr :: ReportsGetRole -> Constr #

dataTypeOf :: ReportsGetRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ReportsGetRole Source # 
Read ReportsGetRole Source # 
Show ReportsGetRole Source # 
Generic ReportsGetRole Source # 

Associated Types

type Rep ReportsGetRole :: * -> * #

Hashable ReportsGetRole Source # 
ToJSON ReportsGetRole Source # 
FromJSON ReportsGetRole Source # 
FromHttpApiData ReportsGetRole Source # 
ToHttpApiData ReportsGetRole Source # 
type Rep ReportsGetRole Source # 
type Rep ReportsGetRole = D1 (MetaData "ReportsGetRole" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "RGRAdvertisers" PrefixI False) U1) (C1 (MetaCons "RGRPublishers" PrefixI False) U1))

Events

data Events Source #

Instances

Eq Events Source # 

Methods

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

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

Data Events Source # 

Methods

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

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

toConstr :: Events -> Constr #

dataTypeOf :: Events -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Events Source # 
Generic Events Source # 

Associated Types

type Rep Events :: * -> * #

Methods

from :: Events -> Rep Events x #

to :: Rep Events x -> Events #

ToJSON Events Source # 
FromJSON Events Source # 
type Rep Events Source # 
type Rep Events = D1 (MetaData "Events" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "Events'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_eveNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_eveKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_eveItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Event]))))))

events :: Events Source #

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

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

eveNextPageToken :: Lens' Events (Maybe Text) Source #

The 'pageToken' to pass to the next request to get the next page, if there are more to retrieve.

eveKind :: Lens' Events Text Source #

The kind for a page of events.

eveItems :: Lens' Events [Event] Source #

The event list.

LinkSpecialOffers

data LinkSpecialOffers Source #

Special offers on the link.

See: linkSpecialOffers smart constructor.

Instances

Eq LinkSpecialOffers Source # 
Data LinkSpecialOffers Source # 

Methods

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

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

toConstr :: LinkSpecialOffers -> Constr #

dataTypeOf :: LinkSpecialOffers -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LinkSpecialOffers Source # 
Generic LinkSpecialOffers Source # 
ToJSON LinkSpecialOffers Source # 
FromJSON LinkSpecialOffers Source # 
type Rep LinkSpecialOffers Source # 
type Rep LinkSpecialOffers = D1 (MetaData "LinkSpecialOffers" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "LinkSpecialOffers'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_lsoFreeShippingMin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Money))) (S1 (MetaSel (Just Symbol "_lsoPercentOff") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))) ((:*:) (S1 (MetaSel (Just Symbol "_lsoPriceCut") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Money))) (S1 (MetaSel (Just Symbol "_lsoPriceCutMin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Money))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_lsoPercentOffMin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Money))) (S1 (MetaSel (Just Symbol "_lsoFreeShipping") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_lsoPromotionCodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_lsoFreeGift") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))))

linkSpecialOffers :: LinkSpecialOffers Source #

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

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

lsoFreeShippingMin :: Lens' LinkSpecialOffers (Maybe Money) Source #

Minimum purchase amount for free shipping promotion

lsoPercentOff :: Lens' LinkSpecialOffers (Maybe Double) Source #

Percent off on the purchase

lsoPriceCut :: Lens' LinkSpecialOffers (Maybe Money) Source #

Price cut on the purchase

lsoPriceCutMin :: Lens' LinkSpecialOffers (Maybe Money) Source #

Minimum purchase amount for price cut promotion

lsoPercentOffMin :: Lens' LinkSpecialOffers (Maybe Money) Source #

Minimum purchase amount for percent off promotion

lsoFreeShipping :: Lens' LinkSpecialOffers (Maybe Bool) Source #

Whether there is free shipping

lsoPromotionCodes :: Lens' LinkSpecialOffers [Text] Source #

List of promotion code associated with the link

lsoFreeGift :: Lens' LinkSpecialOffers (Maybe Bool) Source #

Whether there is a free gift

Publishers

data Publishers Source #

Instances

Eq Publishers Source # 
Data Publishers Source # 

Methods

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

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

toConstr :: Publishers -> Constr #

dataTypeOf :: Publishers -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Publishers Source # 
Generic Publishers Source # 

Associated Types

type Rep Publishers :: * -> * #

ToJSON Publishers Source # 
FromJSON Publishers Source # 
type Rep Publishers Source # 
type Rep Publishers = D1 (MetaData "Publishers" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "Publishers'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_pKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_pItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Publisher]))))))

publishers :: Publishers Source #

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

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

pNextPageToken :: Lens' Publishers (Maybe Text) Source #

The 'pageToken' to pass to the next request to get the next page, if there are more to retrieve.

pKind :: Lens' Publishers Text Source #

The kind for a page of entities.

pItems :: Lens' Publishers [Publisher] Source #

The entity list.

Advertiser

data Advertiser Source #

An AdvertiserResource.

See: advertiser smart constructor.

Instances

Eq Advertiser Source # 
Data Advertiser Source # 

Methods

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

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

toConstr :: Advertiser -> Constr #

dataTypeOf :: Advertiser -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Advertiser Source # 
Generic Advertiser Source # 

Associated Types

type Rep Advertiser :: * -> * #

ToJSON Advertiser Source # 
FromJSON Advertiser Source # 
type Rep Advertiser Source # 
type Rep Advertiser = D1 (MetaData "Advertiser" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "Advertiser'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_advAllowPublisherCreatedLinks") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_advContactPhone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_advContactEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_advStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_advLogoURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_advKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_advCategory") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_advSiteURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_advPayoutRank") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_advJoinDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_advDefaultLinkId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_advRedirectDomains") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))) ((:*:) (S1 (MetaSel (Just Symbol "_advName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_advProductFeedsEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_advMerchantCenterIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64])))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_advEpcSevenDayAverage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Money))) ((:*:) (S1 (MetaSel (Just Symbol "_advItem") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Advertiser))) (S1 (MetaSel (Just Symbol "_advId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) (S1 (MetaSel (Just Symbol "_advEpcNinetyDayAverage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Money))) ((:*:) (S1 (MetaSel (Just Symbol "_advCommissionDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_advDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))))

advAllowPublisherCreatedLinks :: Lens' Advertiser (Maybe Bool) Source #

True if the advertiser allows publisher created links, otherwise false.

advContactPhone :: Lens' Advertiser (Maybe Text) Source #

Phone that this advertiser would like publishers to contact them with.

advContactEmail :: Lens' Advertiser (Maybe Text) Source #

Email that this advertiser would like publishers to contact them with.

advStatus :: Lens' Advertiser (Maybe Text) Source #

The status of the requesting publisher's relationship this advertiser.

advLogoURL :: Lens' Advertiser (Maybe Text) Source #

URL to the logo this advertiser uses on the Google Affiliate Network.

advKind :: Lens' Advertiser Text Source #

The kind for an advertiser.

advCategory :: Lens' Advertiser (Maybe Text) Source #

Category that this advertiser belongs to. A valid list of categories can be found here: http://www.google.com/support/affiliatenetwork/advertiser/bin/answer.py?hl=en&answer=107581

advSiteURL :: Lens' Advertiser (Maybe Text) Source #

URL of the website this advertiser advertises from.

advPayoutRank :: Lens' Advertiser (Maybe Text) Source #

A rank based on commissions paid to publishers over the past 90 days. A number between 1 and 4 where 4 means the top quartile (most money paid) and 1 means the bottom quartile (least money paid).

advJoinDate :: Lens' Advertiser (Maybe UTCTime) Source #

Date that this advertiser was approved as a Google Affiliate Network advertiser.

advDefaultLinkId :: Lens' Advertiser (Maybe Int64) Source #

The default link id for this advertiser.

advRedirectDomains :: Lens' Advertiser [Text] Source #

List of redirect URLs for this advertiser

advName :: Lens' Advertiser (Maybe Text) Source #

The name of this advertiser.

advProductFeedsEnabled :: Lens' Advertiser (Maybe Bool) Source #

Allows advertisers to submit product listings to Google Product Search.

advMerchantCenterIds :: Lens' Advertiser [Int64] Source #

List of merchant center ids for this advertiser

advEpcSevenDayAverage :: Lens' Advertiser (Maybe Money) Source #

The sum of fees paid to publishers divided by the total number of clicks over the past seven days. This value should be multiplied by 100 at the time of display.

advItem :: Lens' Advertiser (Maybe Advertiser) Source #

The requested advertiser.

advId :: Lens' Advertiser (Maybe Int64) Source #

The ID of this advertiser.

advEpcNinetyDayAverage :: Lens' Advertiser (Maybe Money) Source #

The sum of fees paid to publishers divided by the total number of clicks over the past three months. This value should be multiplied by 100 at the time of display.

advCommissionDuration :: Lens' Advertiser (Maybe Int32) Source #

The longest possible length of a commission (how long the cookies on the customer's browser last before they expire).

advDescription :: Lens' Advertiser (Maybe Text) Source #

Description of the website the advertiser advertises from.

CcOffer

data CcOffer Source #

A credit card offer. There are many possible result fields. We provide two different views of the data, or "projections." The "full" projection includes every result field. And the "summary" projection, which is the default, includes a smaller subset of the fields. The fields included in the summary projection are marked as such in their descriptions.

See: ccOffer smart constructor.

Instances

Eq CcOffer Source # 

Methods

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

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

Data CcOffer Source # 

Methods

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

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

toConstr :: CcOffer -> Constr #

dataTypeOf :: CcOffer -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CcOffer Source # 
Generic CcOffer Source # 

Associated Types

type Rep CcOffer :: * -> * #

Methods

from :: CcOffer -> Rep CcOffer x #

to :: Rep CcOffer x -> CcOffer #

ToJSON CcOffer Source # 
FromJSON CcOffer Source # 
type Rep CcOffer Source # 
type Rep CcOffer = D1 (MetaData "CcOffer" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "CcOffer'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cMinimumFinanceCharge") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cTrackingURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cProhibitedCategories") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cBalanceComputationMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cInitialSetupAndProcessingFee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cReturnedPaymentFee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cAgeMinimumDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cVariableRatesUpdateFrequency") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cCreditLimitMin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))) ((:*:) (S1 (MetaSel (Just Symbol "_cTravelInsurance") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cApprovedCategories") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cAnnualFeeDisplay") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cOverLimitFee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cMaxPurchaseRate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_cAgeMinimum") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cVariableRatesLastUpdated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cIntroCashAdvanceTerms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cIssuerWebsite") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cLuggageInsurance") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_cRewardsHaveBlackoutDates") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_cDisclaimer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cAdditionalCardHolderFee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cExistingCustomerOnly") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_cEmergencyInsurance") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cNetwork") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cCashAdvanceTerms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cStatementCopyFee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cAprDisplay") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cOffersImmediateCashReward") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_cRewards") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CcOfferRewardsItem])))))))) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cCardType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cImageURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cCreditLimitMax") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_cLandingPageURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cAnnualFee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_cRewardsExpire") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_cFirstYearAnnualFee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_cCarRentalInsurance") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cPurchaseRateAdditionalDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cOfferId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cGracePeriodDisplay") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cIntroPurchaseTerms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cCreditRatingDisplay") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cBalanceTransferTerms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cLatePaymentFee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cCardBenefits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cIssuer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cCardName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cMinPurchaseRate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_cFraudLiability") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cForeignCurrencyTransactionFee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cExtendedWarranty") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cAnnualRewardMaximum") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_cIssuerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cIntroBalanceTransferTerms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cDefaultFees") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CcOfferDefaultFeesItem])))) ((:*:) (S1 (MetaSel (Just Symbol "_cAdditionalCardBenefits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_cRewardUnit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cBonusRewards") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CcOfferBonusRewardsItem]))) (S1 (MetaSel (Just Symbol "_cFlightAccidentInsurance") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cRewardPartner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cPurchaseRateType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))))

cMinimumFinanceCharge :: Lens' CcOffer (Maybe Text) Source #

Text describing how much missing the grace period will cost.

cTrackingURL :: Lens' CcOffer (Maybe Text) Source #

The link to ping to register a click on this offer. A summary field.

cProhibitedCategories :: Lens' CcOffer [Text] Source #

Categories in which the issuer does not wish the card to be displayed. A summary field.

cBalanceComputationMethod :: Lens' CcOffer (Maybe Text) Source #

Text describing how the balance is computed. A summary field.

cInitialSetupAndProcessingFee :: Lens' CcOffer (Maybe Text) Source #

Fee for setting up the card.

cReturnedPaymentFee :: Lens' CcOffer (Maybe Text) Source #

Text describing the fee for a payment that doesn't clear. A summary field.

cAgeMinimumDetails :: Lens' CcOffer (Maybe Text) Source #

Text describing the details of the age minimum restriction.

cVariableRatesUpdateFrequency :: Lens' CcOffer (Maybe Text) Source #

How often variable rates are updated.

cCreditLimitMin :: Lens' CcOffer (Maybe Double) Source #

The low end for credit limits the issuer imposes on recipients of this card.

cTravelInsurance :: Lens' CcOffer (Maybe Text) Source #

If you get coverage when you use the card for the given activity, this field describes it.

cApprovedCategories :: Lens' CcOffer [Text] Source #

Possible categories for this card, eg "Low Interest" or "Good." A summary field.

cAnnualFeeDisplay :: Lens' CcOffer (Maybe Text) Source #

Text describing the annual fee, including any difference for the first year. A summary field.

cOverLimitFee :: Lens' CcOffer (Maybe Text) Source #

Fee for exceeding the card's charge limit.

cMaxPurchaseRate :: Lens' CcOffer (Maybe Double) Source #

The highest interest rate the issuer charges on this card. Expressed as an absolute number, not as a percentage.

cAgeMinimum :: Lens' CcOffer (Maybe Double) Source #

The youngest a recipient of this card may be.

cVariableRatesLastUpdated :: Lens' CcOffer (Maybe Text) Source #

When variable rates were last updated.

cIntroCashAdvanceTerms :: Lens' CcOffer (Maybe Text) Source #

Text describing the terms for introductory period cash advances. A summary field.

cIssuerWebsite :: Lens' CcOffer (Maybe Text) Source #

The generic link to the issuer's site.

cLuggageInsurance :: Lens' CcOffer (Maybe Text) Source #

If you get coverage when you use the card for the given activity, this field describes it.

cKind :: Lens' CcOffer Text Source #

The kind for one credit card offer. A summary field.

cRewardsHaveBlackoutDates :: Lens' CcOffer (Maybe Bool) Source #

For airline miles rewards, tells whether blackout dates apply to the miles.

cDisclaimer :: Lens' CcOffer (Maybe Text) Source #

A notice that, if present, is referenced via an asterisk by many of the other summary fields. If this field is present, it will always start with an asterisk ("*"), and must be prominently displayed with the offer. A summary field.

cAdditionalCardHolderFee :: Lens' CcOffer (Maybe Text) Source #

Any extra fees levied on card holders.

cExistingCustomerOnly :: Lens' CcOffer (Maybe Bool) Source #

Whether this card is only available to existing customers of the issuer.

cEmergencyInsurance :: Lens' CcOffer (Maybe Text) Source #

If you get coverage when you use the card for the given activity, this field describes it.

cNetwork :: Lens' CcOffer (Maybe Text) Source #

Which network (eg Visa) the card belongs to. A summary field.

cCashAdvanceTerms :: Lens' CcOffer (Maybe Text) Source #

Text describing the terms for cash advances. A summary field.

cStatementCopyFee :: Lens' CcOffer (Maybe Text) Source #

Fee for requesting a copy of your statement.

cAprDisplay :: Lens' CcOffer (Maybe Text) Source #

Text describing the purchase APR. A summary field.

cOffersImmediateCashReward :: Lens' CcOffer (Maybe Bool) Source #

Whether a cash reward program lets you get cash back sooner than end of year or other longish period.

cRewards :: Lens' CcOffer [CcOfferRewardsItem] Source #

For cards with rewards programs, detailed rules about how the program works.

cCardType :: Lens' CcOffer (Maybe Text) Source #

What kind of credit card this is, for example secured or unsecured.

cImageURL :: Lens' CcOffer (Maybe Text) Source #

The link to the image of the card that is shown on Connect Commerce. A summary field.

cCreditLimitMax :: Lens' CcOffer (Maybe Double) Source #

The high end for credit limits the issuer imposes on recipients of this card.

cLandingPageURL :: Lens' CcOffer (Maybe Text) Source #

The link to the issuer's page for this card. A summary field.

cAnnualFee :: Lens' CcOffer (Maybe Double) Source #

The ongoing annual fee, in dollars.

cRewardsExpire :: Lens' CcOffer (Maybe Bool) Source #

Whether accumulated rewards ever expire.

cFirstYearAnnualFee :: Lens' CcOffer (Maybe Double) Source #

The annual fee for the first year, if different from the ongoing fee. Optional.

cCarRentalInsurance :: Lens' CcOffer (Maybe Text) Source #

If you get coverage when you use the card for the given activity, this field describes it.

cPurchaseRateAdditionalDetails :: Lens' CcOffer (Maybe Text) Source #

Text describing any additional details for the purchase rate. A summary field.

cOfferId :: Lens' CcOffer (Maybe Text) Source #

This offer's ID. A summary field.

cGracePeriodDisplay :: Lens' CcOffer (Maybe Text) Source #

Text describing the grace period before finance charges apply. A summary field.

cIntroPurchaseTerms :: Lens' CcOffer (Maybe Text) Source #

Text describing the terms for introductory period purchases. A summary field.

cCreditRatingDisplay :: Lens' CcOffer (Maybe Text) Source #

Text describing the credit ratings required for recipients of this card, for example "Excellent/Good." A summary field.

cBalanceTransferTerms :: Lens' CcOffer (Maybe Text) Source #

Text describing the terms for balance transfers. A summary field.

cLatePaymentFee :: Lens' CcOffer (Maybe Text) Source #

Text describing how much a late payment will cost, eg "up to $35." A summary field.

cCardBenefits :: Lens' CcOffer [Text] Source #

A list of what the issuer thinks are the most important benefits of the card. Usually summarizes the rewards program, if there is one. A summary field.

cIssuer :: Lens' CcOffer (Maybe Text) Source #

Name of card issuer. A summary field.

cCardName :: Lens' CcOffer (Maybe Text) Source #

The issuer's name for the card, including any trademark or service mark designators. A summary field.

cMinPurchaseRate :: Lens' CcOffer (Maybe Double) Source #

The lowest interest rate the issuer charges on this card. Expressed as an absolute number, not as a percentage.

cFraudLiability :: Lens' CcOffer (Maybe Text) Source #

If you get coverage when you use the card for the given activity, this field describes it.

cForeignCurrencyTransactionFee :: Lens' CcOffer (Maybe Text) Source #

Fee for each transaction involving a foreign currency.

cExtendedWarranty :: Lens' CcOffer (Maybe Text) Source #

If you get coverage when you use the card for the given activity, this field describes it.

cAnnualRewardMaximum :: Lens' CcOffer (Maybe Double) Source #

The largest number of units you may accumulate in a year.

cIssuerId :: Lens' CcOffer (Maybe Text) Source #

The Google Affiliate Network ID of the advertiser making this offer.

cIntroBalanceTransferTerms :: Lens' CcOffer (Maybe Text) Source #

Text describing the terms for introductory period balance transfers. A summary field.

cDefaultFees :: Lens' CcOffer [CcOfferDefaultFeesItem] Source #

Fees for defaulting on your payments.

cAdditionalCardBenefits :: Lens' CcOffer [Text] Source #

More marketing copy about the card's benefits. A summary field.

cRewardUnit :: Lens' CcOffer (Maybe Text) Source #

For cards with rewards programs, the unit of reward. For example, miles, cash back, points.

cBonusRewards :: Lens' CcOffer [CcOfferBonusRewardsItem] Source #

For cards with rewards programs, extra circumstances whereby additional rewards may be granted.

cFlightAccidentInsurance :: Lens' CcOffer (Maybe Text) Source #

If you get coverage when you use the card for the given activity, this field describes it.

cRewardPartner :: Lens' CcOffer (Maybe Text) Source #

The company that redeems the rewards, if different from the issuer.

Links

data Links Source #

links :: Links Source #

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

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

linNextPageToken :: Lens' Links (Maybe Text) Source #

The next page token.

linKind :: Lens' Links Text Source #

The kind for a page of links.

linItems :: Lens' Links [Link] Source #

The links.

Publisher

data Publisher Source #

A PublisherResource.

See: publisher smart constructor.

Instances

Eq Publisher Source # 
Data Publisher Source # 

Methods

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

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

toConstr :: Publisher -> Constr #

dataTypeOf :: Publisher -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Publisher Source # 
Generic Publisher Source # 

Associated Types

type Rep Publisher :: * -> * #

ToJSON Publisher Source # 
FromJSON Publisher Source # 
type Rep Publisher Source # 
type Rep Publisher = D1 (MetaData "Publisher" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "Publisher'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pubStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pubKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_pubPayoutRank") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_pubJoinDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_pubClassification") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pubName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_pubEpcSevenDayAverage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Money))) (S1 (MetaSel (Just Symbol "_pubItem") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Publisher))))) ((:*:) (S1 (MetaSel (Just Symbol "_pubId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_pubEpcNinetyDayAverage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Money))) (S1 (MetaSel (Just Symbol "_pubSites") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))))))

publisher :: Publisher Source #

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

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

pubStatus :: Lens' Publisher (Maybe Text) Source #

The status of the requesting advertiser's relationship with this publisher.

pubKind :: Lens' Publisher Text Source #

The kind for a publisher.

pubPayoutRank :: Lens' Publisher (Maybe Text) Source #

A rank based on commissions paid to this publisher over the past 90 days. A number between 1 and 4 where 4 means the top quartile (most money paid) and 1 means the bottom quartile (least money paid).

pubJoinDate :: Lens' Publisher (Maybe UTCTime) Source #

Date that this publisher was approved as a Google Affiliate Network publisher.

pubClassification :: Lens' Publisher (Maybe Text) Source #

Classification that this publisher belongs to. See this link for all publisher classifications: http://www.google.com/support/affiliatenetwork/advertiser/bin/answer.py?hl=en&answer=107625&ctx=cb&src=cb&cbid=-k5fihzthfaik&cbrank=4

pubName :: Lens' Publisher (Maybe Text) Source #

The name of this publisher.

pubEpcSevenDayAverage :: Lens' Publisher (Maybe Money) Source #

The sum of fees paid to this publisher divided by the total number of clicks over the past seven days. Values are multiplied by 100 for display purposes.

pubItem :: Lens' Publisher (Maybe Publisher) Source #

The requested publisher.

pubId :: Lens' Publisher (Maybe Int64) Source #

The ID of this publisher.

pubEpcNinetyDayAverage :: Lens' Publisher (Maybe Money) Source #

The sum of fees paid to this publisher divided by the total number of clicks over the past three months. Values are multiplied by 100 for display purposes.

pubSites :: Lens' Publisher [Text] Source #

Websites that this publisher uses to advertise.

CcOfferRewardsItem

data CcOfferRewardsItem Source #

Instances

Eq CcOfferRewardsItem Source # 
Data CcOfferRewardsItem Source # 

Methods

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

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

toConstr :: CcOfferRewardsItem -> Constr #

dataTypeOf :: CcOfferRewardsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CcOfferRewardsItem Source # 
Generic CcOfferRewardsItem Source # 
ToJSON CcOfferRewardsItem Source # 
FromJSON CcOfferRewardsItem Source # 
type Rep CcOfferRewardsItem Source # 
type Rep CcOfferRewardsItem = D1 (MetaData "CcOfferRewardsItem" "Network.Google.Affiliates.Types.Product" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) (C1 (MetaCons "CcOfferRewardsItem'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_coriAmount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) ((:*:) (S1 (MetaSel (Just Symbol "_coriExpirationMonths") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_coriCategory") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_coriAdditionalDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_coriMaxRewardTier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_coriMinRewardTier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))))))

ccOfferRewardsItem :: CcOfferRewardsItem Source #

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

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

coriAmount :: Lens' CcOfferRewardsItem (Maybe Double) Source #

The number of units rewarded per purchase dollar.

coriExpirationMonths :: Lens' CcOfferRewardsItem (Maybe Double) Source #

How long rewards granted by this rule last.

coriCategory :: Lens' CcOfferRewardsItem (Maybe Text) Source #

The kind of purchases covered by this rule.

coriAdditionalDetails :: Lens' CcOfferRewardsItem (Maybe Text) Source #

Other limits, for example, if this rule only applies during an introductory period.

coriMaxRewardTier :: Lens' CcOfferRewardsItem (Maybe Double) Source #

The maximum purchase amount in the given category for this rule to apply.

coriMinRewardTier :: Lens' CcOfferRewardsItem (Maybe Double) Source #

The minimum purchase amount in the given category before this rule applies.

LinksListRelationshipStatus

data LinksListRelationshipStatus Source #

The status of the relationship.

Constructors

LLRSApproved
approved
LLRSAvailable
available

Instances

Enum LinksListRelationshipStatus Source # 
Eq LinksListRelationshipStatus Source # 
Data LinksListRelationshipStatus Source # 

Methods

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

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

toConstr :: LinksListRelationshipStatus -> Constr #

dataTypeOf :: LinksListRelationshipStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LinksListRelationshipStatus Source # 
Read LinksListRelationshipStatus Source # 
Show LinksListRelationshipStatus Source # 
Generic LinksListRelationshipStatus Source # 
Hashable LinksListRelationshipStatus Source # 
ToJSON LinksListRelationshipStatus Source # 
FromJSON LinksListRelationshipStatus Source # 
FromHttpApiData LinksListRelationshipStatus Source # 
ToHttpApiData LinksListRelationshipStatus Source # 
type Rep LinksListRelationshipStatus Source # 
type Rep LinksListRelationshipStatus = D1 (MetaData "LinksListRelationshipStatus" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "LLRSApproved" PrefixI False) U1) (C1 (MetaCons "LLRSAvailable" PrefixI False) U1))

EventsListStatus

data EventsListStatus Source #

Filters out all events that do not have the given status. Valid values: 'active', 'canceled'. Optional.

Constructors

ELSActive

active Event is currently active.

ELSCanceled

canceled Event is currently canceled.

Instances

Enum EventsListStatus Source # 
Eq EventsListStatus Source # 
Data EventsListStatus Source # 

Methods

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

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

toConstr :: EventsListStatus -> Constr #

dataTypeOf :: EventsListStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EventsListStatus Source # 
Read EventsListStatus Source # 
Show EventsListStatus Source # 
Generic EventsListStatus Source # 
Hashable EventsListStatus Source # 
ToJSON EventsListStatus Source # 
FromJSON EventsListStatus Source # 
FromHttpApiData EventsListStatus Source # 
ToHttpApiData EventsListStatus Source # 
type Rep EventsListStatus Source # 
type Rep EventsListStatus = D1 (MetaData "EventsListStatus" "Network.Google.Affiliates.Types.Sum" "gogol-affiliates-0.3.0-JnD32GtQi0c8cNZneHyDCL" False) ((:+:) (C1 (MetaCons "ELSActive" PrefixI False) U1) (C1 (MetaCons "ELSCanceled" PrefixI False) U1))