gogol-dfareporting-0.1.0: Google DCM/DFA Reporting And Trafficking 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.DFAReporting.Types

Contents

Description

 

Synopsis

Service Configuration

dFAReportingService :: ServiceConfig Source #

Default request referring to version 'v2.5' of the DCM/DFA Reporting And Trafficking API. This contains the host and root path used as a starting point for constructing service requests.

OAuth Scopes

dFAReportingScope :: Proxy '["https://www.googleapis.com/auth/dfareporting"] Source #

View and manage DoubleClick for Advertisers reports

ddmconversionsScope :: Proxy '["https://www.googleapis.com/auth/ddmconversions"] Source #

Manage DoubleClick Digital Marketing conversions

dfatraffickingScope :: Proxy '["https://www.googleapis.com/auth/dfatrafficking"] Source #

View and manage your DoubleClick Campaign Manager's (DCM) display ad campaigns

PlacementsListSortOrder

data PlacementsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

Ascending
ASCENDING
Descending
DESCENDING

Instances

Enum PlacementsListSortOrder Source # 
Eq PlacementsListSortOrder Source # 
Data PlacementsListSortOrder Source # 

Methods

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

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

toConstr :: PlacementsListSortOrder -> Constr #

dataTypeOf :: PlacementsListSortOrder -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PlacementsListSortOrder Source # 
Read PlacementsListSortOrder Source # 
Show PlacementsListSortOrder Source # 
Generic PlacementsListSortOrder Source # 
Hashable PlacementsListSortOrder Source # 
ToJSON PlacementsListSortOrder Source # 
FromJSON PlacementsListSortOrder Source # 
FromHttpApiData PlacementsListSortOrder Source # 
ToHttpApiData PlacementsListSortOrder Source # 
type Rep PlacementsListSortOrder Source # 
type Rep PlacementsListSortOrder = D1 (MetaData "PlacementsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Ascending" PrefixI False) U1) (C1 (MetaCons "Descending" PrefixI False) U1))

DateRangeRelativeDateRange

data DateRangeRelativeDateRange Source #

The date range relative to the date of when the report is run.

Constructors

Last24Months
LAST_24_MONTHS
Last30Days
LAST_30_DAYS
Last365Days
LAST_365_DAYS
Last7Days
LAST_7_DAYS
Last90Days
LAST_90_DAYS
MonthToDate
MONTH_TO_DATE
PreviousMonth
PREVIOUS_MONTH
PreviousQuarter
PREVIOUS_QUARTER
PreviousWeek
PREVIOUS_WEEK
PreviousYear
PREVIOUS_YEAR
QuarterToDate
QUARTER_TO_DATE
Today
TODAY
WeekToDate
WEEK_TO_DATE
YearToDate
YEAR_TO_DATE
Yesterday
YESTERDAY

Instances

Enum DateRangeRelativeDateRange Source # 
Eq DateRangeRelativeDateRange Source # 
Data DateRangeRelativeDateRange Source # 

Methods

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

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

toConstr :: DateRangeRelativeDateRange -> Constr #

dataTypeOf :: DateRangeRelativeDateRange -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DateRangeRelativeDateRange Source # 
Read DateRangeRelativeDateRange Source # 
Show DateRangeRelativeDateRange Source # 
Generic DateRangeRelativeDateRange Source # 
Hashable DateRangeRelativeDateRange Source # 
ToJSON DateRangeRelativeDateRange Source # 
FromJSON DateRangeRelativeDateRange Source # 
FromHttpApiData DateRangeRelativeDateRange Source # 
ToHttpApiData DateRangeRelativeDateRange Source # 
type Rep DateRangeRelativeDateRange Source # 
type Rep DateRangeRelativeDateRange = D1 (MetaData "DateRangeRelativeDateRange" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Last24Months" PrefixI False) U1) ((:+:) (C1 (MetaCons "Last30Days" PrefixI False) U1) (C1 (MetaCons "Last365Days" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Last7Days" PrefixI False) U1) (C1 (MetaCons "Last90Days" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MonthToDate" PrefixI False) U1) (C1 (MetaCons "PreviousMonth" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "PreviousQuarter" PrefixI False) U1) (C1 (MetaCons "PreviousWeek" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PreviousYear" PrefixI False) U1) (C1 (MetaCons "QuarterToDate" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Today" PrefixI False) U1) (C1 (MetaCons "WeekToDate" PrefixI False) U1)) ((:+:) (C1 (MetaCons "YearToDate" PrefixI False) U1) (C1 (MetaCons "Yesterday" PrefixI False) U1)))))

AdvertisersListSortField

data AdvertisersListSortField Source #

Field by which to sort the list.

Constructors

ID
ID
Name
NAME

Instances

Enum AdvertisersListSortField Source # 
Eq AdvertisersListSortField Source # 
Data AdvertisersListSortField Source # 

Methods

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

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

toConstr :: AdvertisersListSortField -> Constr #

dataTypeOf :: AdvertisersListSortField -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AdvertisersListSortField Source # 
Read AdvertisersListSortField Source # 
Show AdvertisersListSortField Source # 
Generic AdvertisersListSortField Source # 
Hashable AdvertisersListSortField Source # 
ToJSON AdvertisersListSortField Source # 
FromJSON AdvertisersListSortField Source # 
FromHttpApiData AdvertisersListSortField Source # 
ToHttpApiData AdvertisersListSortField Source # 
type Rep AdvertisersListSortField Source # 
type Rep AdvertisersListSortField = D1 (MetaData "AdvertisersListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ID" PrefixI False) U1) (C1 (MetaCons "Name" PrefixI False) U1))

CreativeFieldsListSortOrder

data CreativeFieldsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

CFLSOAscending
ASCENDING
CFLSODescending
DESCENDING

Instances

Enum CreativeFieldsListSortOrder Source # 
Eq CreativeFieldsListSortOrder Source # 
Data CreativeFieldsListSortOrder Source # 

Methods

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

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

toConstr :: CreativeFieldsListSortOrder -> Constr #

dataTypeOf :: CreativeFieldsListSortOrder -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CreativeFieldsListSortOrder Source # 
Read CreativeFieldsListSortOrder Source # 
Show CreativeFieldsListSortOrder Source # 
Generic CreativeFieldsListSortOrder Source # 
Hashable CreativeFieldsListSortOrder Source # 
ToJSON CreativeFieldsListSortOrder Source # 
FromJSON CreativeFieldsListSortOrder Source # 
FromHttpApiData CreativeFieldsListSortOrder Source # 
ToHttpApiData CreativeFieldsListSortOrder Source # 
type Rep CreativeFieldsListSortOrder Source # 
type Rep CreativeFieldsListSortOrder = D1 (MetaData "CreativeFieldsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CFLSOAscending" PrefixI False) U1) (C1 (MetaCons "CFLSODescending" PrefixI False) U1))

FileList

data FileList Source #

Represents the list of File resources.

See: fileList smart constructor.

Instances

Eq FileList Source # 
Data FileList Source # 

Methods

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

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

toConstr :: FileList -> Constr #

dataTypeOf :: FileList -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FileList Source # 
Generic FileList Source # 

Associated Types

type Rep FileList :: * -> * #

Methods

from :: FileList -> Rep FileList x #

to :: Rep FileList x -> FileList #

ToJSON FileList Source # 
FromJSON FileList Source # 
type Rep FileList Source # 
type Rep FileList = D1 (MetaData "FileList" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FileList'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_flEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_flNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_flKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_flItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [File]))))))

fileList :: FileList Source #

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

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

flEtag :: Lens' FileList (Maybe Text) Source #

The eTag of this response for caching purposes.

flNextPageToken :: Lens' FileList (Maybe Text) Source #

Continuation token used to page through files. To retrieve the next page of results, set the next request's "pageToken" to the value of this field. The page token is only valid for a limited amount of time and should not be persisted.

flKind :: Lens' FileList Text Source #

The kind of list this is, in this case dfareporting#fileList.

flItems :: Lens' FileList [File] Source #

The files returned in this response.

OptimizationActivity

data OptimizationActivity Source #

Creative optimization activity.

See: optimizationActivity smart constructor.

Instances

Eq OptimizationActivity Source # 
Data OptimizationActivity Source # 

Methods

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

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

toConstr :: OptimizationActivity -> Constr #

dataTypeOf :: OptimizationActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Show OptimizationActivity Source # 
Generic OptimizationActivity Source # 
ToJSON OptimizationActivity Source # 
FromJSON OptimizationActivity Source # 
type Rep OptimizationActivity Source # 
type Rep OptimizationActivity = D1 (MetaData "OptimizationActivity" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "OptimizationActivity'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_oaWeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_oaFloodlightActivityId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_oaFloodlightActivityIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))))))

optimizationActivity :: OptimizationActivity Source #

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

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

oaWeight :: Lens' OptimizationActivity (Maybe Int32) Source #

Weight associated with this optimization. Must be greater than 1. The weight assigned will be understood in proportion to the weights assigned to the other optimization activities.

oaFloodlightActivityId :: Lens' OptimizationActivity (Maybe Int64) Source #

Floodlight activity ID of this optimization activity. This is a required field.

oaFloodlightActivityIdDimensionValue :: Lens' OptimizationActivity (Maybe DimensionValue) Source #

Dimension value for the ID of the floodlight activity. This is a read-only, auto-generated field.

ListPopulationClause

data ListPopulationClause Source #

A group clause made up of list population terms representing constraints joined by ORs.

See: listPopulationClause smart constructor.

Instances

Eq ListPopulationClause Source # 
Data ListPopulationClause Source # 

Methods

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

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

toConstr :: ListPopulationClause -> Constr #

dataTypeOf :: ListPopulationClause -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ListPopulationClause Source # 
Generic ListPopulationClause Source # 
ToJSON ListPopulationClause Source # 
FromJSON ListPopulationClause Source # 
type Rep ListPopulationClause Source # 
type Rep ListPopulationClause = D1 (MetaData "ListPopulationClause" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" True) (C1 (MetaCons "ListPopulationClause'" PrefixI True) (S1 (MetaSel (Just Symbol "_lpcTerms") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [ListPopulationTerm]))))

listPopulationClause :: ListPopulationClause Source #

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

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

lpcTerms :: Lens' ListPopulationClause [ListPopulationTerm] Source #

Terms of this list population clause. Each clause is made up of list population terms representing constraints and are joined by ORs.

CreativeCustomEvent

data CreativeCustomEvent Source #

Creative Custom Event.

See: creativeCustomEvent smart constructor.

Instances

Eq CreativeCustomEvent Source # 
Data CreativeCustomEvent Source # 

Methods

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

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

toConstr :: CreativeCustomEvent -> Constr #

dataTypeOf :: CreativeCustomEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CreativeCustomEvent Source # 
Generic CreativeCustomEvent Source # 
ToJSON CreativeCustomEvent Source # 
FromJSON CreativeCustomEvent Source # 
type Rep CreativeCustomEvent Source # 
type Rep CreativeCustomEvent = D1 (MetaData "CreativeCustomEvent" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeCustomEvent'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cceAdvertiserCustomEventId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_cceAdvertiserCustomEventType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeCustomEventAdvertiserCustomEventType)))) ((:*:) (S1 (MetaSel (Just Symbol "_cceAdvertiserCustomEventName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cceExitURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cceTargetType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeCustomEventTargetType)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ccePopupWindowProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PopupWindowProperties))) (S1 (MetaSel (Just Symbol "_cceVideoReportingId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_cceArtworkLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cceArtworkType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeCustomEventArtworkType))))))))

cceAdvertiserCustomEventId :: Lens' CreativeCustomEvent (Maybe Int64) Source #

Unique ID of this event used by DDM Reporting and Data Transfer. This is a read-only field.

cceExitURL :: Lens' CreativeCustomEvent (Maybe Text) Source #

Exit URL of the event. This field is used only for exit events.

ccePopupWindowProperties :: Lens' CreativeCustomEvent (Maybe PopupWindowProperties) Source #

Properties for rich media popup windows. This field is used only for exit events.

cceVideoReportingId :: Lens' CreativeCustomEvent (Maybe Text) Source #

Video reporting ID, used to differentiate multiple videos in a single creative. This is a read-only field.

cceId :: Lens' CreativeCustomEvent (Maybe Int64) Source #

ID of this event. This is a required field and should not be modified after insertion.

cceArtworkLabel :: Lens' CreativeCustomEvent (Maybe Text) Source #

Artwork label column, used to link events in DCM back to events in Studio. This is a required field and should not be modified after insertion.

cceArtworkType :: Lens' CreativeCustomEvent (Maybe CreativeCustomEventArtworkType) Source #

Artwork type used by the creative.This is a read-only field.

ClickTag

data ClickTag Source #

Creative Click Tag.

See: clickTag smart constructor.

Instances

Eq ClickTag Source # 
Data ClickTag Source # 

Methods

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

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

toConstr :: ClickTag -> Constr #

dataTypeOf :: ClickTag -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ClickTag Source # 
Generic ClickTag Source # 

Associated Types

type Rep ClickTag :: * -> * #

Methods

from :: ClickTag -> Rep ClickTag x #

to :: Rep ClickTag x -> ClickTag #

ToJSON ClickTag Source # 
FromJSON ClickTag Source # 
type Rep ClickTag Source # 
type Rep ClickTag = D1 (MetaData "ClickTag" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ClickTag'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ctValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ctName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ctEventName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

clickTag :: ClickTag Source #

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

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

ctValue :: Lens' ClickTag (Maybe Text) Source #

Parameter value for the specified click tag. This field contains a click-through url.

ctName :: Lens' ClickTag (Maybe Text) Source #

Parameter name for the specified click tag. For ENHANCED_IMAGE creative assets, this field must match the value of the creative asset's creativeAssetId.name field.

ctEventName :: Lens' ClickTag (Maybe Text) Source #

Advertiser event name associated with the click tag. This field is used by ENHANCED_BANNER, ENHANCED_IMAGE, and HTML5_BANNER creatives.

CampaignsListResponse

data CampaignsListResponse Source #

Campaign List Response

See: campaignsListResponse smart constructor.

Instances

Eq CampaignsListResponse Source # 
Data CampaignsListResponse Source # 

Methods

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

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

toConstr :: CampaignsListResponse -> Constr #

dataTypeOf :: CampaignsListResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CampaignsListResponse Source # 
Generic CampaignsListResponse Source # 
ToJSON CampaignsListResponse Source # 
FromJSON CampaignsListResponse Source # 
type Rep CampaignsListResponse Source # 
type Rep CampaignsListResponse = D1 (MetaData "CampaignsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CampaignsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_clrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_clrCampaigns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Campaign]))) (S1 (MetaSel (Just Symbol "_clrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

campaignsListResponse :: CampaignsListResponse Source #

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

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

clrNextPageToken :: Lens' CampaignsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

clrKind :: Lens' CampaignsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#campaignsListResponse".

GeoTargeting

data GeoTargeting Source #

Geographical Targeting.

See: geoTargeting smart constructor.

Instances

Eq GeoTargeting Source # 
Data GeoTargeting Source # 

Methods

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

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

toConstr :: GeoTargeting -> Constr #

dataTypeOf :: GeoTargeting -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GeoTargeting Source # 
Generic GeoTargeting Source # 

Associated Types

type Rep GeoTargeting :: * -> * #

ToJSON GeoTargeting Source # 
FromJSON GeoTargeting Source # 
type Rep GeoTargeting Source # 
type Rep GeoTargeting = D1 (MetaData "GeoTargeting" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "GeoTargeting'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gtRegions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Region]))) ((:*:) (S1 (MetaSel (Just Symbol "_gtCountries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Country]))) (S1 (MetaSel (Just Symbol "_gtCities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [City]))))) ((:*:) (S1 (MetaSel (Just Symbol "_gtMetros") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Metro]))) ((:*:) (S1 (MetaSel (Just Symbol "_gtExcludeCountries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_gtPostalCodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PostalCode])))))))

geoTargeting :: GeoTargeting Source #

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

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

gtRegions :: Lens' GeoTargeting [Region] Source #

Regions to be targeted. For each region only dartId is required. The other fields are populated automatically when the ad is inserted or updated. If targeting a region, do not target or exclude the country of the region.

gtCountries :: Lens' GeoTargeting [Country] Source #

Countries to be targeted or excluded from targeting, depending on the setting of the excludeCountries field. For each country only dartId is required. The other fields are populated automatically when the ad is inserted or updated. If targeting or excluding a country, do not target regions, cities, metros, or postal codes in the same country.

gtCities :: Lens' GeoTargeting [City] Source #

Cities to be targeted. For each city only dartId is required. The other fields are populated automatically when the ad is inserted or updated. If targeting a city, do not target or exclude the country of the city, and do not target the metro or region of the city.

gtMetros :: Lens' GeoTargeting [Metro] Source #

Metros to be targeted. For each metro only dmaId is required. The other fields are populated automatically when the ad is inserted or updated. If targeting a metro, do not target or exclude the country of the metro.

gtExcludeCountries :: Lens' GeoTargeting (Maybe Bool) Source #

Whether or not to exclude the countries in the countries field from targeting. If false, the countries field refers to countries which will be targeted by the ad.

gtPostalCodes :: Lens' GeoTargeting [PostalCode] Source #

Postal codes to be targeted. For each postal code only id is required. The other fields are populated automatically when the ad is inserted or updated. If targeting a postal code, do not target or exclude the country of the postal code.

UserRolesListSortField

data UserRolesListSortField Source #

Field by which to sort the list.

Constructors

URLSFID
ID
URLSFName
NAME

Instances

Enum UserRolesListSortField Source # 
Eq UserRolesListSortField Source # 
Data UserRolesListSortField Source # 

Methods

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

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

toConstr :: UserRolesListSortField -> Constr #

dataTypeOf :: UserRolesListSortField -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UserRolesListSortField Source # 
Read UserRolesListSortField Source # 
Show UserRolesListSortField Source # 
Generic UserRolesListSortField Source # 
Hashable UserRolesListSortField Source # 
ToJSON UserRolesListSortField Source # 
FromJSON UserRolesListSortField Source # 
FromHttpApiData UserRolesListSortField Source # 
ToHttpApiData UserRolesListSortField Source # 
type Rep UserRolesListSortField Source # 
type Rep UserRolesListSortField = D1 (MetaData "UserRolesListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "URLSFID" PrefixI False) U1) (C1 (MetaCons "URLSFName" PrefixI False) U1))

ReachReportCompatibleFields

data ReachReportCompatibleFields Source #

Represents fields that are compatible to be selected for a report of type "REACH".

See: reachReportCompatibleFields smart constructor.

Instances

Eq ReachReportCompatibleFields Source # 
Data ReachReportCompatibleFields Source # 

Methods

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

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

toConstr :: ReachReportCompatibleFields -> Constr #

dataTypeOf :: ReachReportCompatibleFields -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ReachReportCompatibleFields Source # 
Generic ReachReportCompatibleFields Source # 
ToJSON ReachReportCompatibleFields Source # 
FromJSON ReachReportCompatibleFields Source # 
type Rep ReachReportCompatibleFields Source # 
type Rep ReachReportCompatibleFields = D1 (MetaData "ReachReportCompatibleFields" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ReachReportCompatibleFields'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rrcfMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Metric]))) ((:*:) (S1 (MetaSel (Just Symbol "_rrcfReachByFrequencyMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Metric]))) (S1 (MetaSel (Just Symbol "_rrcfKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rrcfDimensionFilters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension]))) ((:*:) (S1 (MetaSel (Just Symbol "_rrcfPivotedActivityMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Metric]))) (S1 (MetaSel (Just Symbol "_rrcfDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension])))))))

reachReportCompatibleFields :: ReachReportCompatibleFields Source #

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

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

rrcfMetrics :: Lens' ReachReportCompatibleFields [Metric] Source #

Metrics which are compatible to be selected in the "metricNames" section of the report.

rrcfReachByFrequencyMetrics :: Lens' ReachReportCompatibleFields [Metric] Source #

Metrics which are compatible to be selected in the "reachByFrequencyMetricNames" section of the report.

rrcfKind :: Lens' ReachReportCompatibleFields Text Source #

The kind of resource this is, in this case dfareporting#reachReportCompatibleFields.

rrcfDimensionFilters :: Lens' ReachReportCompatibleFields [Dimension] Source #

Dimensions which are compatible to be selected in the "dimensionFilters" section of the report.

rrcfPivotedActivityMetrics :: Lens' ReachReportCompatibleFields [Metric] Source #

Metrics which are compatible to be selected as activity metrics to pivot on in the "activities" section of the report.

rrcfDimensions :: Lens' ReachReportCompatibleFields [Dimension] Source #

Dimensions which are compatible to be selected in the "dimensions" section of the report.

Browser

data Browser Source #

Contains information about a browser that can be targeted by ads.

See: browser smart constructor.

Instances

Eq Browser Source # 

Methods

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

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

Data Browser Source # 

Methods

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

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

toConstr :: Browser -> Constr #

dataTypeOf :: Browser -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Browser Source # 
Generic Browser Source # 

Associated Types

type Rep Browser :: * -> * #

Methods

from :: Browser -> Rep Browser x #

to :: Rep Browser x -> Browser #

ToJSON Browser Source # 
FromJSON Browser Source # 
type Rep Browser Source # 

browser :: Browser Source #

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

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

bMinorVersion :: Lens' Browser (Maybe Text) Source #

Minor version number (number after first dot on left) of this browser. For example, for Chrome 5.0.375.86 beta, this field should be set to 0. An asterisk (*) may be used to target any version number, and a question mark (?) may be used to target cases where the version number cannot be identified. For example, Chrome *.* targets any version of Chrome: 1.2, 2.5, 3.5, and so on. Chrome 3.* targets Chrome 3.1, 3.5, but not 4.0. Firefox ?.? targets cases where the ad server knows the browser is Firefox but can't tell which version it is.

bKind :: Lens' Browser Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#browser".

bBrowserVersionId :: Lens' Browser (Maybe Int64) Source #

ID referring to this grouping of browser and version numbers. This is the ID used for targeting.

bMajorVersion :: Lens' Browser (Maybe Text) Source #

Major version number (leftmost number) of this browser. For example, for Chrome 5.0.376.86 beta, this field should be set to 5. An asterisk (*) may be used to target any version number, and a question mark (?) may be used to target cases where the version number cannot be identified. For example, Chrome *.* targets any version of Chrome: 1.2, 2.5, 3.5, and so on. Chrome 3.* targets Chrome 3.1, 3.5, but not 4.0. Firefox ?.? targets cases where the ad server knows the browser is Firefox but can't tell which version it is.

bName :: Lens' Browser (Maybe Text) Source #

Name of this browser.

bDartId :: Lens' Browser (Maybe Int64) Source #

DART ID of this browser. This is the ID used when generating reports.

FloodlightActivityTagFormat

data FloodlightActivityTagFormat Source #

Tag format type for the floodlight activity. If left blank, the tag format will default to HTML.

Constructors

HTML
HTML
Xhtml
XHTML

Instances

Enum FloodlightActivityTagFormat Source # 
Eq FloodlightActivityTagFormat Source # 
Data FloodlightActivityTagFormat Source # 

Methods

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

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

toConstr :: FloodlightActivityTagFormat -> Constr #

dataTypeOf :: FloodlightActivityTagFormat -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FloodlightActivityTagFormat Source # 
Read FloodlightActivityTagFormat Source # 
Show FloodlightActivityTagFormat Source # 
Generic FloodlightActivityTagFormat Source # 
Hashable FloodlightActivityTagFormat Source # 
ToJSON FloodlightActivityTagFormat Source # 
FromJSON FloodlightActivityTagFormat Source # 
FromHttpApiData FloodlightActivityTagFormat Source # 
ToHttpApiData FloodlightActivityTagFormat Source # 
type Rep FloodlightActivityTagFormat Source # 
type Rep FloodlightActivityTagFormat = D1 (MetaData "FloodlightActivityTagFormat" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "HTML" PrefixI False) U1) (C1 (MetaCons "Xhtml" PrefixI False) U1))

OrderDocumentsListSortOrder

data OrderDocumentsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

ODLSOAscending
ASCENDING
ODLSODescending
DESCENDING

Instances

Enum OrderDocumentsListSortOrder Source # 
Eq OrderDocumentsListSortOrder Source # 
Data OrderDocumentsListSortOrder Source # 

Methods

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

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

toConstr :: OrderDocumentsListSortOrder -> Constr #

dataTypeOf :: OrderDocumentsListSortOrder -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OrderDocumentsListSortOrder Source # 
Read OrderDocumentsListSortOrder Source # 
Show OrderDocumentsListSortOrder Source # 
Generic OrderDocumentsListSortOrder Source # 
Hashable OrderDocumentsListSortOrder Source # 
ToJSON OrderDocumentsListSortOrder Source # 
FromJSON OrderDocumentsListSortOrder Source # 
FromHttpApiData OrderDocumentsListSortOrder Source # 
ToHttpApiData OrderDocumentsListSortOrder Source # 
type Rep OrderDocumentsListSortOrder Source # 
type Rep OrderDocumentsListSortOrder = D1 (MetaData "OrderDocumentsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ODLSOAscending" PrefixI False) U1) (C1 (MetaCons "ODLSODescending" PrefixI False) U1))

CreativeGroupAssignment

data CreativeGroupAssignment Source #

Creative Group Assignment.

See: creativeGroupAssignment smart constructor.

Instances

Eq CreativeGroupAssignment Source # 
Data CreativeGroupAssignment Source # 

Methods

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

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

toConstr :: CreativeGroupAssignment -> Constr #

dataTypeOf :: CreativeGroupAssignment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CreativeGroupAssignment Source # 
Generic CreativeGroupAssignment Source # 
ToJSON CreativeGroupAssignment Source # 
FromJSON CreativeGroupAssignment Source # 
type Rep CreativeGroupAssignment Source # 
type Rep CreativeGroupAssignment = D1 (MetaData "CreativeGroupAssignment" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeGroupAssignment'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cgaCreativeGroupNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeGroupAssignmentCreativeGroupNumber))) (S1 (MetaSel (Just Symbol "_cgaCreativeGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))

creativeGroupAssignment :: CreativeGroupAssignment Source #

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

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

cgaCreativeGroupId :: Lens' CreativeGroupAssignment (Maybe Int64) Source #

ID of the creative group to be assigned.

CreativeAssetRole

data CreativeAssetRole Source #

Role of the asset in relation to creative. Applicable to all but the following creative types: all REDIRECT and TRACKING_TEXT. This is a required field. PRIMARY applies to DISPLAY, FLASH_INPAGE, HTML5_BANNER, IMAGE, DISPLAY_IMAGE_GALLERY, all RICH_MEDIA (which may contain multiple primary assets), and all VPAID creatives. BACKUP_IMAGE applies to FLASH_INPAGE, HTML5_BANNER, all RICH_MEDIA, and all VPAID creatives. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE. ADDITIONAL_IMAGE and ADDITIONAL_FLASH apply to FLASH_INPAGE creatives. OTHER refers to assets from sources other than DCM, such as Studio uploaded assets, applicable to all RICH_MEDIA and all VPAID creatives. PARENT_VIDEO refers to videos uploaded by the user in DCM and is applicable to INSTREAM_VIDEO and VPAID_LINEAR_VIDEO creatives. TRANSCODED_VIDEO refers to videos transcoded by DCM from PARENT_VIDEO assets and is applicable to INSTREAM_VIDEO and VPAID_LINEAR_VIDEO creatives. ALTERNATE_VIDEO refers to the DCM representation of child asset videos from Studio, and is applicable to VPAID_LINEAR_VIDEO creatives. These cannot be added or removed within DCM. For VPAID_LINEAR_VIDEO creatives, PARENT_VIDEO, TRANSCODED_VIDEO and ALTERNATE_VIDEO assets that are marked active serve as backup in case the VPAID creative cannot be served. Only PARENT_VIDEO assets can be added or removed for an INSTREAM_VIDEO or VPAID_LINEAR_VIDEO creative.

Constructors

AdditionalFlash
ADDITIONAL_FLASH
AdditionalImage
ADDITIONAL_IMAGE
AlternateVideo
ALTERNATE_VIDEO
BackupImage
BACKUP_IMAGE
Other
OTHER
ParentVideo
PARENT_VIDEO
Primary
PRIMARY
TranscodedVideo
TRANSCODED_VIDEO

Instances

Enum CreativeAssetRole Source # 
Eq CreativeAssetRole Source # 
Data CreativeAssetRole Source # 

Methods

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

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

toConstr :: CreativeAssetRole -> Constr #

dataTypeOf :: CreativeAssetRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CreativeAssetRole Source # 
Read CreativeAssetRole Source # 
Show CreativeAssetRole Source # 
Generic CreativeAssetRole Source # 
Hashable CreativeAssetRole Source # 
ToJSON CreativeAssetRole Source # 
FromJSON CreativeAssetRole Source # 
FromHttpApiData CreativeAssetRole Source # 
ToHttpApiData CreativeAssetRole Source # 
type Rep CreativeAssetRole Source # 
type Rep CreativeAssetRole = D1 (MetaData "CreativeAssetRole" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "AdditionalFlash" PrefixI False) U1) (C1 (MetaCons "AdditionalImage" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AlternateVideo" PrefixI False) U1) (C1 (MetaCons "BackupImage" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Other" PrefixI False) U1) (C1 (MetaCons "ParentVideo" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Primary" PrefixI False) U1) (C1 (MetaCons "TranscodedVideo" PrefixI False) U1))))

DynamicTargetingKeysListObjectType

data DynamicTargetingKeysListObjectType Source #

Select only dynamic targeting keys with this object type.

Constructors

ObjectAd
OBJECT_AD
ObjectAdvertiser
OBJECT_ADVERTISER
ObjectCreative
OBJECT_CREATIVE
ObjectPlacement
OBJECT_PLACEMENT

Instances

Enum DynamicTargetingKeysListObjectType Source # 
Eq DynamicTargetingKeysListObjectType Source # 
Data DynamicTargetingKeysListObjectType Source # 

Methods

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

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

toConstr :: DynamicTargetingKeysListObjectType -> Constr #

dataTypeOf :: DynamicTargetingKeysListObjectType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DynamicTargetingKeysListObjectType Source # 
Read DynamicTargetingKeysListObjectType Source # 
Show DynamicTargetingKeysListObjectType Source # 
Generic DynamicTargetingKeysListObjectType Source # 
Hashable DynamicTargetingKeysListObjectType Source # 
ToJSON DynamicTargetingKeysListObjectType Source # 
FromJSON DynamicTargetingKeysListObjectType Source # 
FromHttpApiData DynamicTargetingKeysListObjectType Source # 
ToHttpApiData DynamicTargetingKeysListObjectType Source # 
type Rep DynamicTargetingKeysListObjectType Source # 
type Rep DynamicTargetingKeysListObjectType = D1 (MetaData "DynamicTargetingKeysListObjectType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "ObjectAd" PrefixI False) U1) (C1 (MetaCons "ObjectAdvertiser" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ObjectCreative" PrefixI False) U1) (C1 (MetaCons "ObjectPlacement" PrefixI False) U1)))

RecipientDeliveryType

data RecipientDeliveryType Source #

The delivery type for the recipient.

Constructors

Attachment
ATTACHMENT
Link
LINK

Instances

Enum RecipientDeliveryType Source # 
Eq RecipientDeliveryType Source # 
Data RecipientDeliveryType Source # 

Methods

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

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

toConstr :: RecipientDeliveryType -> Constr #

dataTypeOf :: RecipientDeliveryType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RecipientDeliveryType Source # 
Read RecipientDeliveryType Source # 
Show RecipientDeliveryType Source # 
Generic RecipientDeliveryType Source # 
Hashable RecipientDeliveryType Source # 
ToJSON RecipientDeliveryType Source # 
FromJSON RecipientDeliveryType Source # 
FromHttpApiData RecipientDeliveryType Source # 
ToHttpApiData RecipientDeliveryType Source # 
type Rep RecipientDeliveryType Source # 
type Rep RecipientDeliveryType = D1 (MetaData "RecipientDeliveryType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Attachment" PrefixI False) U1) (C1 (MetaCons "Link" PrefixI False) U1))

ThirdPartyTrackingURLThirdPartyURLType

data ThirdPartyTrackingURLThirdPartyURLType Source #

Third-party URL type for in-stream video creatives.

Constructors

ClickTracking
CLICK_TRACKING
Impression
IMPRESSION
RichMediaBackupImpression
RICH_MEDIA_BACKUP_IMPRESSION
RichMediaImpression
RICH_MEDIA_IMPRESSION
RichMediaRmImpression
RICH_MEDIA_RM_IMPRESSION
Survey
SURVEY
VideoComplete
VIDEO_COMPLETE
VideoCustom
VIDEO_CUSTOM
VideoFirstQuartile
VIDEO_FIRST_QUARTILE
VideoFullscreen
VIDEO_FULLSCREEN
VideoMidpoint
VIDEO_MIDPOINT
VideoMute
VIDEO_MUTE
VideoPause
VIDEO_PAUSE
VideoProgress
VIDEO_PROGRESS
VideoRewind
VIDEO_REWIND
VideoSkip
VIDEO_SKIP
VideoStart
VIDEO_START
VideoStop
VIDEO_STOP
VideoThirdQuartile
VIDEO_THIRD_QUARTILE

Instances

Enum ThirdPartyTrackingURLThirdPartyURLType Source # 
Eq ThirdPartyTrackingURLThirdPartyURLType Source # 
Data ThirdPartyTrackingURLThirdPartyURLType Source # 

Methods

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

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

toConstr :: ThirdPartyTrackingURLThirdPartyURLType -> Constr #

dataTypeOf :: ThirdPartyTrackingURLThirdPartyURLType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ThirdPartyTrackingURLThirdPartyURLType Source # 
Read ThirdPartyTrackingURLThirdPartyURLType Source # 
Show ThirdPartyTrackingURLThirdPartyURLType Source # 
Generic ThirdPartyTrackingURLThirdPartyURLType Source # 
Hashable ThirdPartyTrackingURLThirdPartyURLType Source # 
ToJSON ThirdPartyTrackingURLThirdPartyURLType Source # 
FromJSON ThirdPartyTrackingURLThirdPartyURLType Source # 
FromHttpApiData ThirdPartyTrackingURLThirdPartyURLType Source # 
ToHttpApiData ThirdPartyTrackingURLThirdPartyURLType Source # 
type Rep ThirdPartyTrackingURLThirdPartyURLType Source # 
type Rep ThirdPartyTrackingURLThirdPartyURLType = D1 (MetaData "ThirdPartyTrackingURLThirdPartyURLType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ClickTracking" PrefixI False) U1) (C1 (MetaCons "Impression" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RichMediaBackupImpression" PrefixI False) U1) (C1 (MetaCons "RichMediaImpression" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "RichMediaRmImpression" PrefixI False) U1) (C1 (MetaCons "Survey" PrefixI False) U1)) ((:+:) (C1 (MetaCons "VideoComplete" PrefixI False) U1) ((:+:) (C1 (MetaCons "VideoCustom" PrefixI False) U1) (C1 (MetaCons "VideoFirstQuartile" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "VideoFullscreen" PrefixI False) U1) (C1 (MetaCons "VideoMidpoint" PrefixI False) U1)) ((:+:) (C1 (MetaCons "VideoMute" PrefixI False) U1) ((:+:) (C1 (MetaCons "VideoPause" PrefixI False) U1) (C1 (MetaCons "VideoProgress" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "VideoRewind" PrefixI False) U1) (C1 (MetaCons "VideoSkip" PrefixI False) U1)) ((:+:) (C1 (MetaCons "VideoStart" PrefixI False) U1) ((:+:) (C1 (MetaCons "VideoStop" PrefixI False) U1) (C1 (MetaCons "VideoThirdQuartile" PrefixI False) U1))))))

DirectorySiteSettings

data DirectorySiteSettings Source #

Directory Site Settings

See: directorySiteSettings smart constructor.

Instances

Eq DirectorySiteSettings Source # 
Data DirectorySiteSettings Source # 

Methods

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

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

toConstr :: DirectorySiteSettings -> Constr #

dataTypeOf :: DirectorySiteSettings -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DirectorySiteSettings Source # 
Generic DirectorySiteSettings Source # 
ToJSON DirectorySiteSettings Source # 
FromJSON DirectorySiteSettings Source # 
type Rep DirectorySiteSettings Source # 
type Rep DirectorySiteSettings = D1 (MetaData "DirectorySiteSettings" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DirectorySiteSettings'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dssInterstitialPlacementAccepted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_dssDfpSettings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DfpSettings))) (S1 (MetaSel (Just Symbol "_dssVerificationTagOptOut") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dssActiveViewOptOut") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_dssVideoActiveViewOptOut") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_dssInstreamVideoPlacementAccepted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_dssNielsenOCROptOut") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))))

dssInterstitialPlacementAccepted :: Lens' DirectorySiteSettings (Maybe Bool) Source #

Whether this site accepts interstitial ads.

dssVerificationTagOptOut :: Lens' DirectorySiteSettings (Maybe Bool) Source #

Whether this directory site has disabled generation of Verification ins tags.

dssActiveViewOptOut :: Lens' DirectorySiteSettings (Maybe Bool) Source #

Whether this directory site has disabled active view creatives.

dssVideoActiveViewOptOut :: Lens' DirectorySiteSettings (Maybe Bool) Source #

Whether this directory site has disabled active view for in-stream video creatives.

dssInstreamVideoPlacementAccepted :: Lens' DirectorySiteSettings (Maybe Bool) Source #

Whether this site accepts in-stream video ads.

dssNielsenOCROptOut :: Lens' DirectorySiteSettings (Maybe Bool) Source #

Whether this directory site has disabled Nielsen OCR reach ratings.

TargetableRemarketingListsListSortOrder

data TargetableRemarketingListsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

TRLLSOAscending
ASCENDING
TRLLSODescending
DESCENDING

Instances

Enum TargetableRemarketingListsListSortOrder Source # 
Eq TargetableRemarketingListsListSortOrder Source # 
Data TargetableRemarketingListsListSortOrder Source # 

Methods

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

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

toConstr :: TargetableRemarketingListsListSortOrder -> Constr #

dataTypeOf :: TargetableRemarketingListsListSortOrder -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TargetableRemarketingListsListSortOrder Source # 
Read TargetableRemarketingListsListSortOrder Source # 
Show TargetableRemarketingListsListSortOrder Source # 
Generic TargetableRemarketingListsListSortOrder Source # 
Hashable TargetableRemarketingListsListSortOrder Source # 
ToJSON TargetableRemarketingListsListSortOrder Source # 
FromJSON TargetableRemarketingListsListSortOrder Source # 
FromHttpApiData TargetableRemarketingListsListSortOrder Source # 
ToHttpApiData TargetableRemarketingListsListSortOrder Source # 
type Rep TargetableRemarketingListsListSortOrder Source # 
type Rep TargetableRemarketingListsListSortOrder = D1 (MetaData "TargetableRemarketingListsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "TRLLSOAscending" PrefixI False) U1) (C1 (MetaCons "TRLLSODescending" PrefixI False) U1))

CreativeAssetPositionLeftUnit

data CreativeAssetPositionLeftUnit Source #

Offset left unit for an asset. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA.

Constructors

OffSetUnitPercent
OFFSET_UNIT_PERCENT
OffSetUnitPixel
OFFSET_UNIT_PIXEL
OffSetUnitPixelFromCenter
OFFSET_UNIT_PIXEL_FROM_CENTER

Instances

Enum CreativeAssetPositionLeftUnit Source # 
Eq CreativeAssetPositionLeftUnit Source # 
Data CreativeAssetPositionLeftUnit Source # 

Methods

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

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

toConstr :: CreativeAssetPositionLeftUnit -> Constr #

dataTypeOf :: CreativeAssetPositionLeftUnit -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CreativeAssetPositionLeftUnit Source # 
Read CreativeAssetPositionLeftUnit Source # 
Show CreativeAssetPositionLeftUnit Source # 
Generic CreativeAssetPositionLeftUnit Source # 
Hashable CreativeAssetPositionLeftUnit Source # 
ToJSON CreativeAssetPositionLeftUnit Source # 
FromJSON CreativeAssetPositionLeftUnit Source # 
FromHttpApiData CreativeAssetPositionLeftUnit Source # 
ToHttpApiData CreativeAssetPositionLeftUnit Source # 
type Rep CreativeAssetPositionLeftUnit Source # 
type Rep CreativeAssetPositionLeftUnit = D1 (MetaData "CreativeAssetPositionLeftUnit" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "OffSetUnitPercent" PrefixI False) U1) ((:+:) (C1 (MetaCons "OffSetUnitPixel" PrefixI False) U1) (C1 (MetaCons "OffSetUnitPixelFromCenter" PrefixI False) U1)))

PricingScheduleCapCostOption

data PricingScheduleCapCostOption Source #

Placement cap cost option.

Constructors

CapCostCumulative
CAP_COST_CUMULATIVE
CapCostMonthly
CAP_COST_MONTHLY
CapCostNone
CAP_COST_NONE

Instances

Enum PricingScheduleCapCostOption Source # 
Eq PricingScheduleCapCostOption Source # 
Data PricingScheduleCapCostOption Source # 

Methods

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

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

toConstr :: PricingScheduleCapCostOption -> Constr #

dataTypeOf :: PricingScheduleCapCostOption -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PricingScheduleCapCostOption Source # 
Read PricingScheduleCapCostOption Source # 
Show PricingScheduleCapCostOption Source # 
Generic PricingScheduleCapCostOption Source # 
Hashable PricingScheduleCapCostOption Source # 
ToJSON PricingScheduleCapCostOption Source # 
FromJSON PricingScheduleCapCostOption Source # 
FromHttpApiData PricingScheduleCapCostOption Source # 
ToHttpApiData PricingScheduleCapCostOption Source # 
type Rep PricingScheduleCapCostOption Source # 
type Rep PricingScheduleCapCostOption = D1 (MetaData "PricingScheduleCapCostOption" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CapCostCumulative" PrefixI False) U1) ((:+:) (C1 (MetaCons "CapCostMonthly" PrefixI False) U1) (C1 (MetaCons "CapCostNone" PrefixI False) U1)))

ListPopulationRule

data ListPopulationRule Source #

Remarketing List Population Rule.

See: listPopulationRule smart constructor.

Instances

Eq ListPopulationRule Source # 
Data ListPopulationRule Source # 

Methods

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

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

toConstr :: ListPopulationRule -> Constr #

dataTypeOf :: ListPopulationRule -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ListPopulationRule Source # 
Generic ListPopulationRule Source # 
ToJSON ListPopulationRule Source # 
FromJSON ListPopulationRule Source # 
type Rep ListPopulationRule Source # 
type Rep ListPopulationRule = D1 (MetaData "ListPopulationRule" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ListPopulationRule'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_lprFloodlightActivityName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_lprFloodlightActivityId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_lprListPopulationClauses") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ListPopulationClause]))))))

listPopulationRule :: ListPopulationRule Source #

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

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

lprFloodlightActivityName :: Lens' ListPopulationRule (Maybe Text) Source #

Name of floodlight activity associated with this rule. This is a read-only, auto-generated field.

lprFloodlightActivityId :: Lens' ListPopulationRule (Maybe Int64) Source #

Floodlight activity ID associated with this rule. This field can be left blank.

lprListPopulationClauses :: Lens' ListPopulationRule [ListPopulationClause] Source #

Clauses that make up this list population rule. Clauses are joined by ANDs, and the clauses themselves are made up of list population terms which are joined by ORs.

UserRolePermissionAvailability

data UserRolePermissionAvailability Source #

Levels of availability for a user role permission.

Constructors

AccountAlways
ACCOUNT_ALWAYS
AccountByDefault
ACCOUNT_BY_DEFAULT
NotAvailableByDefault
NOT_AVAILABLE_BY_DEFAULT
SubAccountAndAccountAlways
SUBACCOUNT_AND_ACCOUNT_ALWAYS
SubAccountAndAccountByDefault
SUBACCOUNT_AND_ACCOUNT_BY_DEFAULT

Instances

Enum UserRolePermissionAvailability Source # 
Eq UserRolePermissionAvailability Source # 
Data UserRolePermissionAvailability Source # 

Methods

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

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

toConstr :: UserRolePermissionAvailability -> Constr #

dataTypeOf :: UserRolePermissionAvailability -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UserRolePermissionAvailability Source # 
Read UserRolePermissionAvailability Source # 
Show UserRolePermissionAvailability Source # 
Generic UserRolePermissionAvailability Source # 
Hashable UserRolePermissionAvailability Source # 
ToJSON UserRolePermissionAvailability Source # 
FromJSON UserRolePermissionAvailability Source # 
FromHttpApiData UserRolePermissionAvailability Source # 
ToHttpApiData UserRolePermissionAvailability Source # 
type Rep UserRolePermissionAvailability Source # 
type Rep UserRolePermissionAvailability = D1 (MetaData "UserRolePermissionAvailability" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "AccountAlways" PrefixI False) U1) (C1 (MetaCons "AccountByDefault" PrefixI False) U1)) ((:+:) (C1 (MetaCons "NotAvailableByDefault" PrefixI False) U1) ((:+:) (C1 (MetaCons "SubAccountAndAccountAlways" PrefixI False) U1) (C1 (MetaCons "SubAccountAndAccountByDefault" PrefixI False) U1))))

DirectorySiteContactAssignmentVisibility

data DirectorySiteContactAssignmentVisibility Source #

Visibility of this directory site contact assignment. When set to PUBLIC this contact assignment is visible to all account and agency users; when set to PRIVATE it is visible only to the site.

Constructors

Private
PRIVATE
Public
PUBLIC

Instances

Enum DirectorySiteContactAssignmentVisibility Source # 
Eq DirectorySiteContactAssignmentVisibility Source # 
Data DirectorySiteContactAssignmentVisibility Source # 

Methods

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

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

toConstr :: DirectorySiteContactAssignmentVisibility -> Constr #

dataTypeOf :: DirectorySiteContactAssignmentVisibility -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DirectorySiteContactAssignmentVisibility Source # 
Read DirectorySiteContactAssignmentVisibility Source # 
Show DirectorySiteContactAssignmentVisibility Source # 
Generic DirectorySiteContactAssignmentVisibility Source # 
Hashable DirectorySiteContactAssignmentVisibility Source # 
ToJSON DirectorySiteContactAssignmentVisibility Source # 
FromJSON DirectorySiteContactAssignmentVisibility Source # 
FromHttpApiData DirectorySiteContactAssignmentVisibility Source # 
ToHttpApiData DirectorySiteContactAssignmentVisibility Source # 
type Rep DirectorySiteContactAssignmentVisibility Source # 
type Rep DirectorySiteContactAssignmentVisibility = D1 (MetaData "DirectorySiteContactAssignmentVisibility" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Private" PrefixI False) U1) (C1 (MetaCons "Public" PrefixI False) U1))

SizesListResponse

data SizesListResponse Source #

Size List Response

See: sizesListResponse smart constructor.

Instances

Eq SizesListResponse Source # 
Data SizesListResponse Source # 

Methods

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

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

toConstr :: SizesListResponse -> Constr #

dataTypeOf :: SizesListResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SizesListResponse Source # 
Generic SizesListResponse Source # 
ToJSON SizesListResponse Source # 
FromJSON SizesListResponse Source # 
type Rep SizesListResponse Source # 
type Rep SizesListResponse = D1 (MetaData "SizesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "SizesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_slrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_slrSizes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Size])))))

sizesListResponse :: SizesListResponse Source #

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

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

slrKind :: Lens' SizesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#sizesListResponse".

PlacementCompatibility

data PlacementCompatibility Source #

Placement compatibility. DISPLAY and DISPLAY_INTERSTITIAL refer to rendering on desktop, on mobile devices or in mobile apps for regular or interstitial ads respectively. APP and APP_INTERSTITIAL are no longer allowed for new placement insertions. Instead, use DISPLAY or DISPLAY_INTERSTITIAL. IN_STREAM_VIDEO refers to rendering in in-stream video ads developed with the VAST standard. This field is required on insertion.

Constructors

App
APP
AppInterstitial
APP_INTERSTITIAL
Display
DISPLAY
DisplayInterstitial
DISPLAY_INTERSTITIAL
InStreamVideo
IN_STREAM_VIDEO

Instances

Enum PlacementCompatibility Source # 
Eq PlacementCompatibility Source # 
Data PlacementCompatibility Source # 

Methods

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

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

toConstr :: PlacementCompatibility -> Constr #

dataTypeOf :: PlacementCompatibility -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PlacementCompatibility Source # 
Read PlacementCompatibility Source # 
Show PlacementCompatibility Source # 
Generic PlacementCompatibility Source # 
Hashable PlacementCompatibility Source # 
ToJSON PlacementCompatibility Source # 
FromJSON PlacementCompatibility Source # 
FromHttpApiData PlacementCompatibility Source # 
ToHttpApiData PlacementCompatibility Source # 
type Rep PlacementCompatibility Source # 
type Rep PlacementCompatibility = D1 (MetaData "PlacementCompatibility" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "App" PrefixI False) U1) (C1 (MetaCons "AppInterstitial" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Display" PrefixI False) U1) ((:+:) (C1 (MetaCons "DisplayInterstitial" PrefixI False) U1) (C1 (MetaCons "InStreamVideo" PrefixI False) U1))))

CreativeRotation

data CreativeRotation Source #

Creative Rotation.

See: creativeRotation smart constructor.

Instances

Eq CreativeRotation Source # 
Data CreativeRotation Source # 

Methods

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

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

toConstr :: CreativeRotation -> Constr #

dataTypeOf :: CreativeRotation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CreativeRotation Source # 
Generic CreativeRotation Source # 
ToJSON CreativeRotation Source # 
FromJSON CreativeRotation Source # 
type Rep CreativeRotation Source # 
type Rep CreativeRotation = D1 (MetaData "CreativeRotation" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeRotation'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_crWeightCalculationStrategy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeRotationWeightCalculationStrategy))) (S1 (MetaSel (Just Symbol "_crCreativeAssignments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeAssignment])))) ((:*:) (S1 (MetaSel (Just Symbol "_crCreativeOptimizationConfigurationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_crType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeRotationType))))))

creativeRotation :: CreativeRotation Source #

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

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

crWeightCalculationStrategy :: Lens' CreativeRotation (Maybe CreativeRotationWeightCalculationStrategy) Source #

Strategy for calculating weights. Used with CREATIVE_ROTATION_TYPE_RANDOM.

crCreativeAssignments :: Lens' CreativeRotation [CreativeAssignment] Source #

Creative assignments in this creative rotation.

crCreativeOptimizationConfigurationId :: Lens' CreativeRotation (Maybe Int64) Source #

Creative optimization configuration that is used by this ad. It should refer to one of the existing optimization configurations in the ad's campaign. If it is unset or set to 0, then the campaign's default optimization configuration will be used for this ad.

crType :: Lens' CreativeRotation (Maybe CreativeRotationType) Source #

Type of creative rotation. Can be used to specify whether to use sequential or random rotation.

TechnologyTargeting

data TechnologyTargeting Source #

Technology Targeting.

See: technologyTargeting smart constructor.

Instances

Eq TechnologyTargeting Source # 
Data TechnologyTargeting Source # 

Methods

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

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

toConstr :: TechnologyTargeting -> Constr #

dataTypeOf :: TechnologyTargeting -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TechnologyTargeting Source # 
Generic TechnologyTargeting Source # 
ToJSON TechnologyTargeting Source # 
FromJSON TechnologyTargeting Source # 
type Rep TechnologyTargeting Source # 
type Rep TechnologyTargeting = D1 (MetaData "TechnologyTargeting" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "TechnologyTargeting'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ttMobileCarriers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [MobileCarrier]))) ((:*:) (S1 (MetaSel (Just Symbol "_ttOperatingSystemVersions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [OperatingSystemVersion]))) (S1 (MetaSel (Just Symbol "_ttPlatformTypes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PlatformType]))))) ((:*:) (S1 (MetaSel (Just Symbol "_ttBrowsers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Browser]))) ((:*:) (S1 (MetaSel (Just Symbol "_ttConnectionTypes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ConnectionType]))) (S1 (MetaSel (Just Symbol "_ttOperatingSystems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [OperatingSystem])))))))

technologyTargeting :: TechnologyTargeting Source #

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

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

ttMobileCarriers :: Lens' TechnologyTargeting [MobileCarrier] Source #

Mobile carriers that this ad targets. For each mobile carrier only id is required, and the other fields are populated automatically when the ad is inserted or updated. If targeting a mobile carrier, do not set targeting for any zip codes.

ttOperatingSystemVersions :: Lens' TechnologyTargeting [OperatingSystemVersion] Source #

Operating system versions that this ad targets. To target all versions, use operatingSystems. For each operating system version, only id is required. The other fields are populated automatically when the ad is inserted or updated. If targeting an operating system version, do not set targeting for the corresponding operating system in operatingSystems.

ttPlatformTypes :: Lens' TechnologyTargeting [PlatformType] Source #

Platform types that this ad targets. For example, desktop, mobile, or tablet. For each platform type, only id is required, and the other fields are populated automatically when the ad is inserted or updated.

ttBrowsers :: Lens' TechnologyTargeting [Browser] Source #

Browsers that this ad targets. For each browser either set browserVersionId or dartId along with the version numbers. If both are specified, only browserVersionId will be used.The other fields are populated automatically when the ad is inserted or updated.

ttConnectionTypes :: Lens' TechnologyTargeting [ConnectionType] Source #

Connection types that this ad targets. For each connection type only id is required.The other fields are populated automatically when the ad is inserted or updated.

ttOperatingSystems :: Lens' TechnologyTargeting [OperatingSystem] Source #

Operating systems that this ad targets. To target specific versions, use operatingSystemVersions. For each operating system only dartId is required. The other fields are populated automatically when the ad is inserted or updated. If targeting an operating system, do not set targeting for operating system versions for the same operating system.

ListPopulationTermOperator

data ListPopulationTermOperator Source #

Comparison operator of this term. This field is only relevant when type is left unset or set to CUSTOM_VARIABLE_TERM or REFERRER_TERM.

Constructors

NumEquals
NUM_EQUALS
NumGreaterThan
NUM_GREATER_THAN
NumGreaterThanEqual
NUM_GREATER_THAN_EQUAL
NumLessThan
NUM_LESS_THAN
NumLessThanEqual
NUM_LESS_THAN_EQUAL
StringContains
STRING_CONTAINS
StringEquals
STRING_EQUALS

Instances

Enum ListPopulationTermOperator Source # 
Eq ListPopulationTermOperator Source # 
Data ListPopulationTermOperator Source # 

Methods

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

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

toConstr :: ListPopulationTermOperator -> Constr #

dataTypeOf :: ListPopulationTermOperator -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ListPopulationTermOperator Source # 
Read ListPopulationTermOperator Source # 
Show ListPopulationTermOperator Source # 
Generic ListPopulationTermOperator Source # 
Hashable ListPopulationTermOperator Source # 
ToJSON ListPopulationTermOperator Source # 
FromJSON ListPopulationTermOperator Source # 
FromHttpApiData ListPopulationTermOperator Source # 
ToHttpApiData ListPopulationTermOperator Source # 
type Rep ListPopulationTermOperator Source # 
type Rep ListPopulationTermOperator = D1 (MetaData "ListPopulationTermOperator" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "NumEquals" PrefixI False) U1) ((:+:) (C1 (MetaCons "NumGreaterThan" PrefixI False) U1) (C1 (MetaCons "NumGreaterThanEqual" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "NumLessThan" PrefixI False) U1) (C1 (MetaCons "NumLessThanEqual" PrefixI False) U1)) ((:+:) (C1 (MetaCons "StringContains" PrefixI False) U1) (C1 (MetaCons "StringEquals" PrefixI False) U1))))

PlacementsListPaymentSource

data PlacementsListPaymentSource Source #

Select only placements with this payment source.

Constructors

PlacementAgencyPaid
PLACEMENT_AGENCY_PAID
PlacementPublisherPaid
PLACEMENT_PUBLISHER_PAID

Instances

Enum PlacementsListPaymentSource Source # 
Eq PlacementsListPaymentSource Source # 
Data PlacementsListPaymentSource Source # 

Methods

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

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

toConstr :: PlacementsListPaymentSource -> Constr #

dataTypeOf :: PlacementsListPaymentSource -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PlacementsListPaymentSource Source # 
Read PlacementsListPaymentSource Source # 
Show PlacementsListPaymentSource Source # 
Generic PlacementsListPaymentSource Source # 
Hashable PlacementsListPaymentSource Source # 
ToJSON PlacementsListPaymentSource Source # 
FromJSON PlacementsListPaymentSource Source # 
FromHttpApiData PlacementsListPaymentSource Source # 
ToHttpApiData PlacementsListPaymentSource Source # 
type Rep PlacementsListPaymentSource Source # 
type Rep PlacementsListPaymentSource = D1 (MetaData "PlacementsListPaymentSource" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PlacementAgencyPaid" PrefixI False) U1) (C1 (MetaCons "PlacementPublisherPaid" PrefixI False) U1))

InventoryItem

data InventoryItem Source #

Represents a buy from the DoubleClick Planning inventory store.

See: inventoryItem smart constructor.

Instances

Eq InventoryItem Source # 
Data InventoryItem Source # 

Methods

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

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

toConstr :: InventoryItem -> Constr #

dataTypeOf :: InventoryItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show InventoryItem Source # 
Generic InventoryItem Source # 

Associated Types

type Rep InventoryItem :: * -> * #

ToJSON InventoryItem Source # 
FromJSON InventoryItem Source # 
type Rep InventoryItem Source # 
type Rep InventoryItem = D1 (MetaData "InventoryItem" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "InventoryItem'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_iiPlacementStrategyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_iiEstimatedClickThroughRate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_iiPricing") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Pricing))) ((:*:) (S1 (MetaSel (Just Symbol "_iiKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_iiAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_iiRfpId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_iiContentCategoryId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_iiInPlan") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_iiAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_iiName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_iiAdSlots") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AdSlot]))) (S1 (MetaSel (Just Symbol "_iiNegotiationChannelId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_iiLastModifiedInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo))) ((:*:) (S1 (MetaSel (Just Symbol "_iiId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_iiEstimatedConversionRate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_iiProjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_iiSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_iiType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe InventoryItemType))) ((:*:) (S1 (MetaSel (Just Symbol "_iiOrderId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_iiSiteId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))))))

iiPlacementStrategyId :: Lens' InventoryItem (Maybe Int64) Source #

Placement strategy ID of this inventory item.

iiEstimatedClickThroughRate :: Lens' InventoryItem (Maybe Int64) Source #

Estimated click-through rate of this inventory item.

iiPricing :: Lens' InventoryItem (Maybe Pricing) Source #

Pricing of this inventory item.

iiKind :: Lens' InventoryItem Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#inventoryItem".

iiAdvertiserId :: Lens' InventoryItem (Maybe Int64) Source #

Advertiser ID of this inventory item.

iiRfpId :: Lens' InventoryItem (Maybe Int64) Source #

RFP ID of this inventory item.

iiContentCategoryId :: Lens' InventoryItem (Maybe Int64) Source #

Content category ID of this inventory item.

iiInPlan :: Lens' InventoryItem (Maybe Bool) Source #

Whether this inventory item is in plan.

iiAccountId :: Lens' InventoryItem (Maybe Int64) Source #

Account ID of this inventory item.

iiName :: Lens' InventoryItem (Maybe Text) Source #

Name of this inventory item. For standalone inventory items, this is the same name as that of its only ad slot. For group inventory items, this can differ from the name of any of its ad slots.

iiAdSlots :: Lens' InventoryItem [AdSlot] Source #

Ad slots of this inventory item. If this inventory item represents a standalone placement, there will be exactly one ad slot. If this inventory item represents a placement group, there will be more than one ad slot, each representing one child placement in that placement group.

iiNegotiationChannelId :: Lens' InventoryItem (Maybe Int64) Source #

Negotiation channel ID of this inventory item.

iiLastModifiedInfo :: Lens' InventoryItem (Maybe LastModifiedInfo) Source #

Information about the most recent modification of this inventory item.

iiId :: Lens' InventoryItem (Maybe Int64) Source #

ID of this inventory item.

iiEstimatedConversionRate :: Lens' InventoryItem (Maybe Int64) Source #

Estimated conversion rate of this inventory item.

iiProjectId :: Lens' InventoryItem (Maybe Int64) Source #

Project ID of this inventory item.

iiSubAccountId :: Lens' InventoryItem (Maybe Int64) Source #

Subaccount ID of this inventory item.

iiOrderId :: Lens' InventoryItem (Maybe Int64) Source #

Order ID of this inventory item.

iiSiteId :: Lens' InventoryItem (Maybe Int64) Source #

ID of the site this inventory item is associated with.

ProjectsListResponse

data ProjectsListResponse Source #

Project List Response

See: projectsListResponse smart constructor.

Instances

Eq ProjectsListResponse Source # 
Data ProjectsListResponse Source # 

Methods

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

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

toConstr :: ProjectsListResponse -> Constr #

dataTypeOf :: ProjectsListResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ProjectsListResponse Source # 
Generic ProjectsListResponse Source # 
ToJSON ProjectsListResponse Source # 
FromJSON ProjectsListResponse Source # 
type Rep ProjectsListResponse Source # 
type Rep ProjectsListResponse = D1 (MetaData "ProjectsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ProjectsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_plrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_plrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_plrProjects") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Project]))))))

projectsListResponse :: ProjectsListResponse Source #

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

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

plrNextPageToken :: Lens' ProjectsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

plrKind :: Lens' ProjectsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#projectsListResponse".

AdsListResponse

data AdsListResponse Source #

Ad List Response

See: adsListResponse smart constructor.

Instances

Eq AdsListResponse Source # 
Data AdsListResponse Source # 

Methods

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

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

toConstr :: AdsListResponse -> Constr #

dataTypeOf :: AdsListResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AdsListResponse Source # 
Generic AdsListResponse Source # 
ToJSON AdsListResponse Source # 
FromJSON AdsListResponse Source # 
type Rep AdsListResponse Source # 
type Rep AdsListResponse = D1 (MetaData "AdsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AdsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_alrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_alrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_alrAds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Ad]))))))

adsListResponse :: AdsListResponse Source #

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

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

alrNextPageToken :: Lens' AdsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

alrKind :: Lens' AdsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#adsListResponse".

alrAds :: Lens' AdsListResponse [Ad] Source #

Ad collection.

ReportsListSortField

data ReportsListSortField Source #

The field by which to sort the list.

Constructors

RLSFID

ID Sort by report ID.

RLSFLastModifiedTime

LAST_MODIFIED_TIME Sort by 'lastModifiedTime' field.

RLSFName

NAME Sort by name of reports.

Instances

Enum ReportsListSortField Source # 
Eq ReportsListSortField Source # 
Data ReportsListSortField Source # 

Methods

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

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

toConstr :: ReportsListSortField -> Constr #

dataTypeOf :: ReportsListSortField -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ReportsListSortField Source # 
Read ReportsListSortField Source # 
Show ReportsListSortField Source # 
Generic ReportsListSortField Source # 
Hashable ReportsListSortField Source # 
ToJSON ReportsListSortField Source # 
FromJSON ReportsListSortField Source # 
FromHttpApiData ReportsListSortField Source # 
ToHttpApiData ReportsListSortField Source # 
type Rep ReportsListSortField Source # 
type Rep ReportsListSortField = D1 (MetaData "ReportsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "RLSFID" PrefixI False) U1) ((:+:) (C1 (MetaCons "RLSFLastModifiedTime" PrefixI False) U1) (C1 (MetaCons "RLSFName" PrefixI False) U1)))

AdSlotCompatibility

data AdSlotCompatibility Source #

Ad slot compatibility. DISPLAY and DISPLAY_INTERSTITIAL refer to rendering either on desktop, mobile devices or in mobile apps for regular or interstitial ads respectively. APP and APP_INTERSTITIAL are for rendering in mobile apps. IN_STREAM_VIDEO refers to rendering in in-stream video ads developed with the VAST standard.

Constructors

ASCApp
APP
ASCAppInterstitial
APP_INTERSTITIAL
ASCDisplay
DISPLAY
ASCDisplayInterstitial
DISPLAY_INTERSTITIAL
ASCInStreamVideo
IN_STREAM_VIDEO

Instances

Enum AdSlotCompatibility Source # 
Eq AdSlotCompatibility Source # 
Data AdSlotCompatibility Source # 

Methods

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

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

toConstr :: AdSlotCompatibility -> Constr #

dataTypeOf :: AdSlotCompatibility -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AdSlotCompatibility Source # 
Read AdSlotCompatibility Source # 
Show AdSlotCompatibility Source # 
Generic AdSlotCompatibility Source # 
Hashable AdSlotCompatibility Source # 
ToJSON AdSlotCompatibility Source # 
FromJSON AdSlotCompatibility Source # 
FromHttpApiData AdSlotCompatibility Source # 
ToHttpApiData AdSlotCompatibility Source # 
type Rep AdSlotCompatibility Source # 
type Rep AdSlotCompatibility = D1 (MetaData "AdSlotCompatibility" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "ASCApp" PrefixI False) U1) (C1 (MetaCons "ASCAppInterstitial" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ASCDisplay" PrefixI False) U1) ((:+:) (C1 (MetaCons "ASCDisplayInterstitial" PrefixI False) U1) (C1 (MetaCons "ASCInStreamVideo" PrefixI False) U1))))

ListPopulationTerm

data ListPopulationTerm Source #

Remarketing List Population Rule Term.

See: listPopulationTerm smart constructor.

Instances

Eq ListPopulationTerm Source # 
Data ListPopulationTerm Source # 

Methods

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

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

toConstr :: ListPopulationTerm -> Constr #

dataTypeOf :: ListPopulationTerm -> DataType #

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

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

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

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

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

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

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

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

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

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

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

listPopulationTerm :: ListPopulationTerm Source #

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

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

lptOperator :: Lens' ListPopulationTerm (Maybe ListPopulationTermOperator) Source #

Comparison operator of this term. This field is only relevant when type is left unset or set to CUSTOM_VARIABLE_TERM or REFERRER_TERM.

lptValue :: Lens' ListPopulationTerm (Maybe Text) Source #

Literal to compare the variable to. This field is only relevant when type is left unset or set to CUSTOM_VARIABLE_TERM or REFERRER_TERM.

lptVariableFriendlyName :: Lens' ListPopulationTerm (Maybe Text) Source #

Friendly name of this term's variable. This is a read-only, auto-generated field. This field is only relevant when type is left unset or set to CUSTOM_VARIABLE_TERM.

lptNegation :: Lens' ListPopulationTerm (Maybe Bool) Source #

Whether to negate the comparison result of this term during rule evaluation. This field is only relevant when type is left unset or set to CUSTOM_VARIABLE_TERM or REFERRER_TERM.

lptVariableName :: Lens' ListPopulationTerm (Maybe Text) Source #

Name of the variable (U1, U2, etc.) being compared in this term. This field is only relevant when type is set to null, CUSTOM_VARIABLE_TERM or REFERRER_TERM.

lptRemarketingListId :: Lens' ListPopulationTerm (Maybe Int64) Source #

ID of the list in question. This field is only relevant when type is set to LIST_MEMBERSHIP_TERM.

lptType :: Lens' ListPopulationTerm (Maybe ListPopulationTermType) Source #

List population term type determines the applicable fields in this object. If left unset or set to CUSTOM_VARIABLE_TERM, then variableName, variableFriendlyName, operator, value, and negation are applicable. If set to LIST_MEMBERSHIP_TERM then remarketingListId and contains are applicable. If set to REFERRER_TERM then operator, value, and negation are applicable.

lptContains :: Lens' ListPopulationTerm (Maybe Bool) Source #

Will be true if the term should check if the user is in the list and false if the term should check if the user is not in the list. This field is only relevant when type is set to LIST_MEMBERSHIP_TERM. False by default.

TagSettings

data TagSettings Source #

Dynamic and Image Tag Settings.

See: tagSettings smart constructor.

Instances

Eq TagSettings Source # 
Data TagSettings Source # 

Methods

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

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

toConstr :: TagSettings -> Constr #

dataTypeOf :: TagSettings -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TagSettings Source # 
Generic TagSettings Source # 

Associated Types

type Rep TagSettings :: * -> * #

ToJSON TagSettings Source # 
FromJSON TagSettings Source # 
type Rep TagSettings Source # 
type Rep TagSettings = D1 (MetaData "TagSettings" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "TagSettings'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tsDynamicTagEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_tsImageTagEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))

tagSettings :: TagSettings Source #

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

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

tsDynamicTagEnabled :: Lens' TagSettings (Maybe Bool) Source #

Whether dynamic floodlight tags are enabled.

tsImageTagEnabled :: Lens' TagSettings (Maybe Bool) Source #

Whether image tags are enabled.

SubAccountsListResponse

data SubAccountsListResponse Source #

Subaccount List Response

See: subAccountsListResponse smart constructor.

Instances

Eq SubAccountsListResponse Source # 
Data SubAccountsListResponse Source # 

Methods

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

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

toConstr :: SubAccountsListResponse -> Constr #

dataTypeOf :: SubAccountsListResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SubAccountsListResponse Source # 
Generic SubAccountsListResponse Source # 
ToJSON SubAccountsListResponse Source # 
FromJSON SubAccountsListResponse Source # 
type Rep SubAccountsListResponse Source # 
type Rep SubAccountsListResponse = D1 (MetaData "SubAccountsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "SubAccountsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_salrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_salrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_salrSubAccounts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SubAccount]))))))

subAccountsListResponse :: SubAccountsListResponse Source #

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

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

salrNextPageToken :: Lens' SubAccountsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

salrKind :: Lens' SubAccountsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#subaccountsListResponse".

CampaignsListSortField

data CampaignsListSortField Source #

Field by which to sort the list.

Constructors

CLSFID
ID
CLSFName
NAME

Instances

Enum CampaignsListSortField Source # 
Eq CampaignsListSortField Source # 
Data CampaignsListSortField Source # 

Methods

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

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

toConstr :: CampaignsListSortField -> Constr #

dataTypeOf :: CampaignsListSortField -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CampaignsListSortField Source # 
Read CampaignsListSortField Source # 
Show CampaignsListSortField Source # 
Generic CampaignsListSortField Source # 
Hashable CampaignsListSortField Source # 
ToJSON CampaignsListSortField Source # 
FromJSON CampaignsListSortField Source # 
FromHttpApiData CampaignsListSortField Source # 
ToHttpApiData CampaignsListSortField Source # 
type Rep CampaignsListSortField Source # 
type Rep CampaignsListSortField = D1 (MetaData "CampaignsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CLSFID" PrefixI False) U1) (C1 (MetaCons "CLSFName" PrefixI False) U1))

DirectorySiteContact

data DirectorySiteContact Source #

Contains properties of a Site Directory contact.

See: directorySiteContact smart constructor.

Instances

Eq DirectorySiteContact Source # 
Data DirectorySiteContact Source # 

Methods

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

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

toConstr :: DirectorySiteContact -> Constr #

dataTypeOf :: DirectorySiteContact -> DataType #

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

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

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

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

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

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

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

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

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

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

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

directorySiteContact :: DirectorySiteContact Source #

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

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

dscEmail :: Lens' DirectorySiteContact (Maybe Text) Source #

Email address of this directory site contact.

dscPhone :: Lens' DirectorySiteContact (Maybe Text) Source #

Phone number of this directory site contact.

dscLastName :: Lens' DirectorySiteContact (Maybe Text) Source #

Last name of this directory site contact.

dscKind :: Lens' DirectorySiteContact Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#directorySiteContact".

dscAddress :: Lens' DirectorySiteContact (Maybe Text) Source #

Address of this directory site contact.

dscFirstName :: Lens' DirectorySiteContact (Maybe Text) Source #

First name of this directory site contact.

dscId :: Lens' DirectorySiteContact (Maybe Int64) Source #

ID of this directory site contact. This is a read-only, auto-generated field.

dscTitle :: Lens' DirectorySiteContact (Maybe Text) Source #

Title or designation of this directory site contact.

RegionsListResponse

data RegionsListResponse Source #

Region List Response

See: regionsListResponse smart constructor.

Instances

Eq RegionsListResponse Source # 
Data RegionsListResponse Source # 

Methods

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

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

toConstr :: RegionsListResponse -> Constr #

dataTypeOf :: RegionsListResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RegionsListResponse Source # 
Generic RegionsListResponse Source # 
ToJSON RegionsListResponse Source # 
FromJSON RegionsListResponse Source # 
type Rep RegionsListResponse Source # 
type Rep RegionsListResponse = D1 (MetaData "RegionsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "RegionsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rlrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_rlrRegions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Region])))))

regionsListResponse :: RegionsListResponse Source #

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

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

rlrKind :: Lens' RegionsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#regionsListResponse".

FloodlightActivityDynamicTag

data FloodlightActivityDynamicTag Source #

Dynamic Tag

See: floodlightActivityDynamicTag smart constructor.

Instances

Eq FloodlightActivityDynamicTag Source # 
Data FloodlightActivityDynamicTag Source # 

Methods

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

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

toConstr :: FloodlightActivityDynamicTag -> Constr #

dataTypeOf :: FloodlightActivityDynamicTag -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FloodlightActivityDynamicTag Source # 
Generic FloodlightActivityDynamicTag Source # 
ToJSON FloodlightActivityDynamicTag Source # 
FromJSON FloodlightActivityDynamicTag Source # 
type Rep FloodlightActivityDynamicTag Source # 
type Rep FloodlightActivityDynamicTag = D1 (MetaData "FloodlightActivityDynamicTag" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FloodlightActivityDynamicTag'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fadtTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_fadtName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_fadtId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

floodlightActivityDynamicTag :: FloodlightActivityDynamicTag Source #

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

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

fadtId :: Lens' FloodlightActivityDynamicTag (Maybe Int64) Source #

ID of this dynamic tag. This is a read-only, auto-generated field.

AccountUserProFileTraffickerType

data AccountUserProFileTraffickerType Source #

Trafficker type of this user profile.

Constructors

ExternalTrafficker
EXTERNAL_TRAFFICKER
InternalNonTrafficker
INTERNAL_NON_TRAFFICKER
InternalTrafficker
INTERNAL_TRAFFICKER

Instances

Enum AccountUserProFileTraffickerType Source # 
Eq AccountUserProFileTraffickerType Source # 
Data AccountUserProFileTraffickerType Source # 

Methods

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

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

toConstr :: AccountUserProFileTraffickerType -> Constr #

dataTypeOf :: AccountUserProFileTraffickerType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AccountUserProFileTraffickerType Source # 
Read AccountUserProFileTraffickerType Source # 
Show AccountUserProFileTraffickerType Source # 
Generic AccountUserProFileTraffickerType Source # 
Hashable AccountUserProFileTraffickerType Source # 
ToJSON AccountUserProFileTraffickerType Source # 
FromJSON AccountUserProFileTraffickerType Source # 
FromHttpApiData AccountUserProFileTraffickerType Source # 
ToHttpApiData AccountUserProFileTraffickerType Source # 
type Rep AccountUserProFileTraffickerType Source # 
type Rep AccountUserProFileTraffickerType = D1 (MetaData "AccountUserProFileTraffickerType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ExternalTrafficker" PrefixI False) U1) ((:+:) (C1 (MetaCons "InternalNonTrafficker" PrefixI False) U1) (C1 (MetaCons "InternalTrafficker" PrefixI False) U1)))

DirectorySite

data DirectorySite Source #

DirectorySites contains properties of a website from the Site Directory. Sites need to be added to an account via the Sites resource before they can be assigned to a placement.

See: directorySite smart constructor.

Instances

Eq DirectorySite Source # 
Data DirectorySite Source # 

Methods

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

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

toConstr :: DirectorySite -> Constr #

dataTypeOf :: DirectorySite -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DirectorySite Source # 
Generic DirectorySite Source # 

Associated Types

type Rep DirectorySite :: * -> * #

ToJSON DirectorySite Source # 
FromJSON DirectorySite Source # 
type Rep DirectorySite Source # 
type Rep DirectorySite = D1 (MetaData "DirectorySite" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DirectorySite'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dsCurrencyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_dsSettings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DirectorySiteSettings))) (S1 (MetaSel (Just Symbol "_dsInterstitialTagFormats") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DirectorySiteInterstitialTagFormatsItem]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dsKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_dsURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_dsIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_dsInpageTagFormats") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DirectorySiteInpageTagFormatsItem])))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dsActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_dsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dsId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dsCountryId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_dsContactAssignments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DirectorySiteContactAssignment])))) ((:*:) (S1 (MetaSel (Just Symbol "_dsDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dsParentId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))))

directorySite :: DirectorySite Source #

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

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

dsCurrencyId :: Lens' DirectorySite (Maybe Int64) Source #

Currency ID of this directory site. Possible values are: - "1" for USD - "2" for GBP - "3" for ESP - "4" for SEK - "5" for CAD - "6" for JPY - "7" for DEM - "8" for AUD - "9" for FRF - "10" for ITL - "11" for DKK - "12" for NOK - "13" for FIM - "14" for ZAR - "15" for IEP - "16" for NLG - "17" for EUR - "18" for KRW - "19" for TWD - "20" for SGD - "21" for CNY - "22" for HKD - "23" for NZD - "24" for MYR - "25" for BRL - "26" for PTE - "27" for MXP - "28" for CLP - "29" for TRY - "30" for ARS - "31" for PEN - "32" for ILS - "33" for CHF - "34" for VEF - "35" for COP - "36" for GTQ - "37" for PLN - "39" for INR - "40" for THB - "41" for IDR - "42" for CZK - "43" for RON - "44" for HUF - "45" for RUB - "46" for AED - "47" for BGN - "48" for HRK

dsInterstitialTagFormats :: Lens' DirectorySite [DirectorySiteInterstitialTagFormatsItem] Source #

Tag types for interstitial placements. Acceptable values are: - "IFRAME_JAVASCRIPT_INTERSTITIAL" - "INTERNAL_REDIRECT_INTERSTITIAL" - "JAVASCRIPT_INTERSTITIAL"

dsKind :: Lens' DirectorySite Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#directorySite".

dsURL :: Lens' DirectorySite (Maybe Text) Source #

URL of this directory site.

dsIdDimensionValue :: Lens' DirectorySite (Maybe DimensionValue) Source #

Dimension value for the ID of this directory site. This is a read-only, auto-generated field.

dsInpageTagFormats :: Lens' DirectorySite [DirectorySiteInpageTagFormatsItem] Source #

Tag types for regular placements. Acceptable values are: - "STANDARD" - "IFRAME_JAVASCRIPT_INPAGE" - "INTERNAL_REDIRECT_INPAGE" - "JAVASCRIPT_INPAGE"

dsActive :: Lens' DirectorySite (Maybe Bool) Source #

Whether this directory site is active.

dsName :: Lens' DirectorySite (Maybe Text) Source #

Name of this directory site.

dsId :: Lens' DirectorySite (Maybe Int64) Source #

ID of this directory site. This is a read-only, auto-generated field.

dsCountryId :: Lens' DirectorySite (Maybe Int64) Source #

Country ID of this directory site.

dsDescription :: Lens' DirectorySite (Maybe Text) Source #

Description of this directory site.

dsParentId :: Lens' DirectorySite (Maybe Int64) Source #

Parent directory site ID.

CreativeAssetMetadataDetectedFeaturesItem

data CreativeAssetMetadataDetectedFeaturesItem Source #

Constructors

ApplicationCache
APPLICATION_CACHE
Audio
AUDIO
Canvas
CANVAS
CanvasText
CANVAS_TEXT
CssAnimations
CSS_ANIMATIONS
CssBackgRoundSize
CSS_BACKGROUND_SIZE
CssBOrderImage
CSS_BORDER_IMAGE
CssBOrderRadius
CSS_BORDER_RADIUS
CssBoxShadow
CSS_BOX_SHADOW
CssColumns
CSS_COLUMNS
CssFlexBox
CSS_FLEX_BOX
CssFontFace
CSS_FONT_FACE
CssGeneratedContent
CSS_GENERATED_CONTENT
CssGradients
CSS_GRADIENTS
CssHsla
CSS_HSLA
CssMultipleBgs
CSS_MULTIPLE_BGS
CssOpacity
CSS_OPACITY
CssReflections
CSS_REFLECTIONS
CssRgba
CSS_RGBA
CssTextShadow
CSS_TEXT_SHADOW
CssTransforms
CSS_TRANSFORMS
CssTRANSFORMS3D
CSS_TRANSFORMS3D
CssTransitions
CSS_TRANSITIONS
DragAndDrop
DRAG_AND_DROP
GeoLocation
GEO_LOCATION
HashChange
HASH_CHANGE
History
HISTORY
IndexedDB
INDEXED_DB
InlineSvg
INLINE_SVG
InputAttrAutocomplete
INPUT_ATTR_AUTOCOMPLETE
InputAttrAutofocus
INPUT_ATTR_AUTOFOCUS
InputAttrList
INPUT_ATTR_LIST
InputAttrMax
INPUT_ATTR_MAX
InputAttrMin
INPUT_ATTR_MIN
InputAttrMultiple
INPUT_ATTR_MULTIPLE
InputAttrPattern
INPUT_ATTR_PATTERN
InputAttrPlaceholder
INPUT_ATTR_PLACEHOLDER
InputAttrRequired
INPUT_ATTR_REQUIRED
InputAttrStep
INPUT_ATTR_STEP
InputTypeColor
INPUT_TYPE_COLOR
InputTypeDate
INPUT_TYPE_DATE
InputTypeDatetime
INPUT_TYPE_DATETIME
InputTypeDatetimeLocal
INPUT_TYPE_DATETIME_LOCAL
InputTypeEmail
INPUT_TYPE_EMAIL
InputTypeMonth
INPUT_TYPE_MONTH
InputTypeNumber
INPUT_TYPE_NUMBER
InputTypeRange
INPUT_TYPE_RANGE
InputTypeSearch
INPUT_TYPE_SEARCH
InputTypeTel
INPUT_TYPE_TEL
InputTypeTime
INPUT_TYPE_TIME
InputTypeURL
INPUT_TYPE_URL
InputTypeWeek
INPUT_TYPE_WEEK
LocalStorage
LOCAL_STORAGE
PostMessage
POST_MESSAGE
SessionStorage
SESSION_STORAGE
Smil
SMIL
SvgClipPaths
SVG_CLIP_PATHS
SvgFeImage
SVG_FE_IMAGE
SvgFilters
SVG_FILTERS
SvgHref
SVG_HREF
Touch
TOUCH
Video
VIDEO
Webgl
WEBGL
WebSockets
WEB_SOCKETS
WebSQLDatabase
WEB_SQL_DATABASE
WebWorkers
WEB_WORKERS

Instances

Enum CreativeAssetMetadataDetectedFeaturesItem Source # 
Eq CreativeAssetMetadataDetectedFeaturesItem Source # 
Data CreativeAssetMetadataDetectedFeaturesItem Source # 

Methods

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

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

toConstr :: CreativeAssetMetadataDetectedFeaturesItem -> Constr #

dataTypeOf :: CreativeAssetMetadataDetectedFeaturesItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CreativeAssetMetadataDetectedFeaturesItem Source # 
Read CreativeAssetMetadataDetectedFeaturesItem Source # 
Show CreativeAssetMetadataDetectedFeaturesItem Source # 
Generic CreativeAssetMetadataDetectedFeaturesItem Source # 
Hashable CreativeAssetMetadataDetectedFeaturesItem Source # 
ToJSON CreativeAssetMetadataDetectedFeaturesItem Source # 
FromJSON CreativeAssetMetadataDetectedFeaturesItem Source # 
FromHttpApiData CreativeAssetMetadataDetectedFeaturesItem Source # 
ToHttpApiData CreativeAssetMetadataDetectedFeaturesItem Source # 
type Rep CreativeAssetMetadataDetectedFeaturesItem Source # 
type Rep CreativeAssetMetadataDetectedFeaturesItem = D1 (MetaData "CreativeAssetMetadataDetectedFeaturesItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ApplicationCache" PrefixI False) U1) (C1 (MetaCons "Audio" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Canvas" PrefixI False) U1) (C1 (MetaCons "CanvasText" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CssAnimations" PrefixI False) U1) (C1 (MetaCons "CssBackgRoundSize" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CssBOrderImage" PrefixI False) U1) (C1 (MetaCons "CssBOrderRadius" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CssBoxShadow" PrefixI False) U1) (C1 (MetaCons "CssColumns" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CssFlexBox" PrefixI False) U1) (C1 (MetaCons "CssFontFace" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CssGeneratedContent" PrefixI False) U1) (C1 (MetaCons "CssGradients" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CssHsla" PrefixI False) U1) (C1 (MetaCons "CssMultipleBgs" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CssOpacity" PrefixI False) U1) (C1 (MetaCons "CssReflections" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CssRgba" PrefixI False) U1) (C1 (MetaCons "CssTextShadow" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CssTransforms" PrefixI False) U1) (C1 (MetaCons "CssTRANSFORMS3D" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CssTransitions" PrefixI False) U1) (C1 (MetaCons "DragAndDrop" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GeoLocation" PrefixI False) U1) (C1 (MetaCons "HashChange" PrefixI False) U1)) ((:+:) (C1 (MetaCons "History" PrefixI False) U1) (C1 (MetaCons "IndexedDB" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "InlineSvg" PrefixI False) U1) (C1 (MetaCons "InputAttrAutocomplete" PrefixI False) U1)) ((:+:) (C1 (MetaCons "InputAttrAutofocus" PrefixI False) U1) ((:+:) (C1 (MetaCons "InputAttrList" PrefixI False) U1) (C1 (MetaCons "InputAttrMax" PrefixI False) U1))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "InputAttrMin" PrefixI False) U1) (C1 (MetaCons "InputAttrMultiple" PrefixI False) U1)) ((:+:) (C1 (MetaCons "InputAttrPattern" PrefixI False) U1) (C1 (MetaCons "InputAttrPlaceholder" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "InputAttrRequired" PrefixI False) U1) (C1 (MetaCons "InputAttrStep" PrefixI False) U1)) ((:+:) (C1 (MetaCons "InputTypeColor" PrefixI False) U1) (C1 (MetaCons "InputTypeDate" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "InputTypeDatetime" PrefixI False) U1) (C1 (MetaCons "InputTypeDatetimeLocal" PrefixI False) U1)) ((:+:) (C1 (MetaCons "InputTypeEmail" PrefixI False) U1) (C1 (MetaCons "InputTypeMonth" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "InputTypeNumber" PrefixI False) U1) (C1 (MetaCons "InputTypeRange" PrefixI False) U1)) ((:+:) (C1 (MetaCons "InputTypeSearch" PrefixI False) U1) (C1 (MetaCons "InputTypeTel" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "InputTypeTime" PrefixI False) U1) (C1 (MetaCons "InputTypeURL" PrefixI False) U1)) ((:+:) (C1 (MetaCons "InputTypeWeek" PrefixI False) U1) (C1 (MetaCons "LocalStorage" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PostMessage" PrefixI False) U1) (C1 (MetaCons "SessionStorage" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Smil" PrefixI False) U1) (C1 (MetaCons "SvgClipPaths" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "SvgFeImage" PrefixI False) U1) (C1 (MetaCons "SvgFilters" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SvgHref" PrefixI False) U1) (C1 (MetaCons "Touch" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Video" PrefixI False) U1) (C1 (MetaCons "Webgl" PrefixI False) U1)) ((:+:) (C1 (MetaCons "WebSockets" PrefixI False) U1) ((:+:) (C1 (MetaCons "WebSQLDatabase" PrefixI False) U1) (C1 (MetaCons "WebWorkers" PrefixI False) U1))))))))

ReportFloodlightCriteriaReportProperties

data ReportFloodlightCriteriaReportProperties Source #

The properties of the report.

See: reportFloodlightCriteriaReportProperties smart constructor.

Instances

Eq ReportFloodlightCriteriaReportProperties Source # 
Data ReportFloodlightCriteriaReportProperties Source # 

Methods

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

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

toConstr :: ReportFloodlightCriteriaReportProperties -> Constr #

dataTypeOf :: ReportFloodlightCriteriaReportProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ReportFloodlightCriteriaReportProperties Source # 
Generic ReportFloodlightCriteriaReportProperties Source # 
ToJSON ReportFloodlightCriteriaReportProperties Source # 
FromJSON ReportFloodlightCriteriaReportProperties Source # 
type Rep ReportFloodlightCriteriaReportProperties Source # 
type Rep ReportFloodlightCriteriaReportProperties = D1 (MetaData "ReportFloodlightCriteriaReportProperties" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ReportFloodlightCriteriaReportProperties'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rfcrpIncludeUnattributedIPConversions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_rfcrpIncludeUnattributedCookieConversions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_rfcrpIncludeAttributedIPConversions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

rfcrpIncludeUnattributedIPConversions :: Lens' ReportFloodlightCriteriaReportProperties (Maybe Bool) Source #

Include conversions that have no associated cookies and no exposures. It’s therefore impossible to know how the user was exposed to your ads during the lookback window prior to a conversion.

rfcrpIncludeUnattributedCookieConversions :: Lens' ReportFloodlightCriteriaReportProperties (Maybe Bool) Source #

Include conversions of users with a DoubleClick cookie but without an exposure. That means the user did not click or see an ad from the advertiser within the Floodlight group, or that the interaction happened outside the lookback window.

rfcrpIncludeAttributedIPConversions :: Lens' ReportFloodlightCriteriaReportProperties (Maybe Bool) Source #

Include conversions that have no cookie, but do have an exposure path.

FloodlightActivityGroup

data FloodlightActivityGroup Source #

Contains properties of a Floodlight activity group.

See: floodlightActivityGroup smart constructor.

Instances

Eq FloodlightActivityGroup Source # 
Data FloodlightActivityGroup Source # 

Methods

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

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

toConstr :: FloodlightActivityGroup -> Constr #

dataTypeOf :: FloodlightActivityGroup -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FloodlightActivityGroup Source # 
Generic FloodlightActivityGroup Source # 
ToJSON FloodlightActivityGroup Source # 
FromJSON FloodlightActivityGroup Source # 
type Rep FloodlightActivityGroup Source # 
type Rep FloodlightActivityGroup = D1 (MetaData "FloodlightActivityGroup" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FloodlightActivityGroup'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_fagTagString") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_fagFloodlightConfigurationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_fagKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_fagAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_fagAdvertiserIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_fagIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_fagAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_fagName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_fagId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) (S1 (MetaSel (Just Symbol "_fagSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_fagType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FloodlightActivityGroupType))) (S1 (MetaSel (Just Symbol "_fagFloodlightConfigurationIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))))))))

fagTagString :: Lens' FloodlightActivityGroup (Maybe Text) Source #

Value of the type= parameter in the floodlight tag, which the ad servers use to identify the activity group that the activity belongs to. This is optional: if empty, a new tag string will be generated for you. This string must be 1 to 8 characters long, with valid characters being [a-z][A-Z][0-9][-][ _ ]. This tag string must also be unique among activity groups of the same floodlight configuration. This field is read-only after insertion.

fagFloodlightConfigurationId :: Lens' FloodlightActivityGroup (Maybe Int64) Source #

Floodlight configuration ID of this floodlight activity group. This is a required field.

fagKind :: Lens' FloodlightActivityGroup Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#floodlightActivityGroup".

fagAdvertiserId :: Lens' FloodlightActivityGroup (Maybe Int64) Source #

Advertiser ID of this floodlight activity group. If this field is left blank, the value will be copied over either from the floodlight configuration's advertiser or from the existing activity group's advertiser.

fagAdvertiserIdDimensionValue :: Lens' FloodlightActivityGroup (Maybe DimensionValue) Source #

Dimension value for the ID of the advertiser. This is a read-only, auto-generated field.

fagIdDimensionValue :: Lens' FloodlightActivityGroup (Maybe DimensionValue) Source #

Dimension value for the ID of this floodlight activity group. This is a read-only, auto-generated field.

fagAccountId :: Lens' FloodlightActivityGroup (Maybe Int64) Source #

Account ID of this floodlight activity group. This is a read-only field that can be left blank.

fagName :: Lens' FloodlightActivityGroup (Maybe Text) Source #

Name of this floodlight activity group. This is a required field. Must be less than 65 characters long and cannot contain quotes.

fagId :: Lens' FloodlightActivityGroup (Maybe Int64) Source #

ID of this floodlight activity group. This is a read-only, auto-generated field.

fagSubAccountId :: Lens' FloodlightActivityGroup (Maybe Int64) Source #

Subaccount ID of this floodlight activity group. This is a read-only field that can be left blank.

fagType :: Lens' FloodlightActivityGroup (Maybe FloodlightActivityGroupType) Source #

Type of the floodlight activity group. This is a required field that is read-only after insertion.

fagFloodlightConfigurationIdDimensionValue :: Lens' FloodlightActivityGroup (Maybe DimensionValue) Source #

Dimension value for the ID of the floodlight configuration. This is a read-only, auto-generated field.

AdsListCompatibility

data AdsListCompatibility Source #

Select default ads with the specified compatibility. Applicable when type is AD_SERVING_DEFAULT_AD. DISPLAY and DISPLAY_INTERSTITIAL refer to rendering either on desktop or on mobile devices for regular or interstitial ads, respectively. APP and APP_INTERSTITIAL are for rendering in mobile apps. IN_STREAM_VIDEO refers to rendering an in-stream video ads developed with the VAST standard.

Constructors

ALCApp
APP
ALCAppInterstitial
APP_INTERSTITIAL
ALCDisplay
DISPLAY
ALCDisplayInterstitial
DISPLAY_INTERSTITIAL
ALCInStreamVideo
IN_STREAM_VIDEO

Instances

Enum AdsListCompatibility Source # 
Eq AdsListCompatibility Source # 
Data AdsListCompatibility Source # 

Methods

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

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

toConstr :: AdsListCompatibility -> Constr #

dataTypeOf :: AdsListCompatibility -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AdsListCompatibility Source # 
Read AdsListCompatibility Source # 
Show AdsListCompatibility Source # 
Generic AdsListCompatibility Source # 
Hashable AdsListCompatibility Source # 
ToJSON AdsListCompatibility Source # 
FromJSON AdsListCompatibility Source # 
FromHttpApiData AdsListCompatibility Source # 
ToHttpApiData AdsListCompatibility Source # 
type Rep AdsListCompatibility Source # 
type Rep AdsListCompatibility = D1 (MetaData "AdsListCompatibility" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "ALCApp" PrefixI False) U1) (C1 (MetaCons "ALCAppInterstitial" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ALCDisplay" PrefixI False) U1) ((:+:) (C1 (MetaCons "ALCDisplayInterstitial" PrefixI False) U1) (C1 (MetaCons "ALCInStreamVideo" PrefixI False) U1))))

CrossDimensionReachReportCompatibleFields

data CrossDimensionReachReportCompatibleFields Source #

Represents fields that are compatible to be selected for a report of type "CROSS_DIMENSION_REACH".

See: crossDimensionReachReportCompatibleFields smart constructor.

Instances

Eq CrossDimensionReachReportCompatibleFields Source # 
Data CrossDimensionReachReportCompatibleFields Source # 

Methods

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

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

toConstr :: CrossDimensionReachReportCompatibleFields -> Constr #

dataTypeOf :: CrossDimensionReachReportCompatibleFields -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CrossDimensionReachReportCompatibleFields Source # 
Generic CrossDimensionReachReportCompatibleFields Source # 
ToJSON CrossDimensionReachReportCompatibleFields Source # 
FromJSON CrossDimensionReachReportCompatibleFields Source # 
type Rep CrossDimensionReachReportCompatibleFields Source # 
type Rep CrossDimensionReachReportCompatibleFields = D1 (MetaData "CrossDimensionReachReportCompatibleFields" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CrossDimensionReachReportCompatibleFields'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cdrrcfMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Metric]))) (S1 (MetaSel (Just Symbol "_cdrrcfBreakdown") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension])))) ((:*:) (S1 (MetaSel (Just Symbol "_cdrrcfKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_cdrrcfDimensionFilters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension]))) (S1 (MetaSel (Just Symbol "_cdrrcfOverlapMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Metric])))))))

crossDimensionReachReportCompatibleFields :: CrossDimensionReachReportCompatibleFields Source #

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

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

cdrrcfMetrics :: Lens' CrossDimensionReachReportCompatibleFields [Metric] Source #

Metrics which are compatible to be selected in the "metricNames" section of the report.

cdrrcfBreakdown :: Lens' CrossDimensionReachReportCompatibleFields [Dimension] Source #

Dimensions which are compatible to be selected in the "breakdown" section of the report.

cdrrcfKind :: Lens' CrossDimensionReachReportCompatibleFields Text Source #

The kind of resource this is, in this case dfareporting#crossDimensionReachReportCompatibleFields.

cdrrcfDimensionFilters :: Lens' CrossDimensionReachReportCompatibleFields [Dimension] Source #

Dimensions which are compatible to be selected in the "dimensionFilters" section of the report.

cdrrcfOverlapMetrics :: Lens' CrossDimensionReachReportCompatibleFields [Metric] Source #

Metrics which are compatible to be selected in the "overlapMetricNames" section of the report.

FsCommand

data FsCommand Source #

FsCommand.

See: fsCommand smart constructor.

Instances

Eq FsCommand Source # 
Data FsCommand Source # 

Methods

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

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

toConstr :: FsCommand -> Constr #

dataTypeOf :: FsCommand -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FsCommand Source # 
Generic FsCommand Source # 

Associated Types

type Rep FsCommand :: * -> * #

ToJSON FsCommand Source # 
FromJSON FsCommand Source # 
type Rep FsCommand Source # 
type Rep FsCommand = D1 (MetaData "FsCommand" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FsCommand'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_fcPositionOption") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FsCommandPositionOption))) (S1 (MetaSel (Just Symbol "_fcLeft") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) ((:*:) (S1 (MetaSel (Just Symbol "_fcWindowHeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_fcWindowWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_fcTop") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))))

fsCommand :: FsCommand Source #

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

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

fcPositionOption :: Lens' FsCommand (Maybe FsCommandPositionOption) Source #

Position in the browser where the window will open.

fcLeft :: Lens' FsCommand (Maybe Int32) Source #

Distance from the left of the browser.Applicable when positionOption is DISTANCE_FROM_TOP_LEFT_CORNER.

fcWindowHeight :: Lens' FsCommand (Maybe Int32) Source #

Height of the window.

fcWindowWidth :: Lens' FsCommand (Maybe Int32) Source #

Width of the window.

fcTop :: Lens' FsCommand (Maybe Int32) Source #

Distance from the top of the browser. Applicable when positionOption is DISTANCE_FROM_TOP_LEFT_CORNER.

PlacementAssignment

data PlacementAssignment Source #

Placement Assignment.

See: placementAssignment smart constructor.

Instances

Eq PlacementAssignment Source # 
Data PlacementAssignment Source # 

Methods

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

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

toConstr :: PlacementAssignment -> Constr #

dataTypeOf :: PlacementAssignment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PlacementAssignment Source # 
Generic PlacementAssignment Source # 
ToJSON PlacementAssignment Source # 
FromJSON PlacementAssignment Source # 
type Rep PlacementAssignment Source # 
type Rep PlacementAssignment = D1 (MetaData "PlacementAssignment" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PlacementAssignment'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_paPlacementId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_paPlacementIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue)))) ((:*:) (S1 (MetaSel (Just Symbol "_paActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_paSSLRequired") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

placementAssignment :: PlacementAssignment Source #

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

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

paPlacementId :: Lens' PlacementAssignment (Maybe Int64) Source #

ID of the placement to be assigned. This is a required field.

paPlacementIdDimensionValue :: Lens' PlacementAssignment (Maybe DimensionValue) Source #

Dimension value for the ID of the placement. This is a read-only, auto-generated field.

paActive :: Lens' PlacementAssignment (Maybe Bool) Source #

Whether this placement assignment is active. When true, the placement will be included in the ad's rotation.

paSSLRequired :: Lens' PlacementAssignment (Maybe Bool) Source #

Whether the placement to be assigned requires SSL. This is a read-only field that is auto-generated when the ad is inserted or updated.

CreativeFieldValue

data CreativeFieldValue Source #

Contains properties of a creative field value.

See: creativeFieldValue smart constructor.

Instances

Eq CreativeFieldValue Source # 
Data CreativeFieldValue Source # 

Methods

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

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

toConstr :: CreativeFieldValue -> Constr #

dataTypeOf :: CreativeFieldValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CreativeFieldValue Source # 
Generic CreativeFieldValue Source # 
ToJSON CreativeFieldValue Source # 
FromJSON CreativeFieldValue Source # 
type Rep CreativeFieldValue Source # 
type Rep CreativeFieldValue = D1 (MetaData "CreativeFieldValue" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeFieldValue'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cfvKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_cfvValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cfvId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

creativeFieldValue :: CreativeFieldValue Source #

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

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

cfvKind :: Lens' CreativeFieldValue Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#creativeFieldValue".

cfvValue :: Lens' CreativeFieldValue (Maybe Text) Source #

Value of this creative field value. It needs to be less than 256 characters in length and unique per creative field.

cfvId :: Lens' CreativeFieldValue (Maybe Int64) Source #

ID of this creative field value. This is a read-only, auto-generated field.

EventTagStatus

data EventTagStatus Source #

Status of this event tag. Must be ENABLED for this event tag to fire. This is a required field.

Constructors

Disabled
DISABLED
Enabled
ENABLED

Instances

Enum EventTagStatus Source # 
Eq EventTagStatus Source # 
Data EventTagStatus Source # 

Methods

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

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

toConstr :: EventTagStatus -> Constr #

dataTypeOf :: EventTagStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EventTagStatus Source # 
Read EventTagStatus Source # 
Show EventTagStatus Source # 
Generic EventTagStatus Source # 

Associated Types

type Rep EventTagStatus :: * -> * #

Hashable EventTagStatus Source # 
ToJSON EventTagStatus Source # 
FromJSON EventTagStatus Source # 
FromHttpApiData EventTagStatus Source # 
ToHttpApiData EventTagStatus Source # 
type Rep EventTagStatus Source # 
type Rep EventTagStatus = D1 (MetaData "EventTagStatus" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Disabled" PrefixI False) U1) (C1 (MetaCons "Enabled" PrefixI False) U1))

SitesListSortField

data SitesListSortField Source #

Field by which to sort the list.

Constructors

SLSFID
ID
SLSFName
NAME

Instances

Enum SitesListSortField Source # 
Eq SitesListSortField Source # 
Data SitesListSortField Source # 

Methods

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

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

toConstr :: SitesListSortField -> Constr #

dataTypeOf :: SitesListSortField -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SitesListSortField Source # 
Read SitesListSortField Source # 
Show SitesListSortField Source # 
Generic SitesListSortField Source # 
Hashable SitesListSortField Source # 
ToJSON SitesListSortField Source # 
FromJSON SitesListSortField Source # 
FromHttpApiData SitesListSortField Source # 
ToHttpApiData SitesListSortField Source # 
type Rep SitesListSortField Source # 
type Rep SitesListSortField = D1 (MetaData "SitesListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "SLSFID" PrefixI False) U1) (C1 (MetaCons "SLSFName" PrefixI False) U1))

DimensionValueRequest

data DimensionValueRequest Source #

Represents a DimensionValuesRequest.

See: dimensionValueRequest smart constructor.

Instances

Eq DimensionValueRequest Source # 
Data DimensionValueRequest Source # 

Methods

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

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

toConstr :: DimensionValueRequest -> Constr #

dataTypeOf :: DimensionValueRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DimensionValueRequest Source # 
Generic DimensionValueRequest Source # 
ToJSON DimensionValueRequest Source # 
FromJSON DimensionValueRequest Source # 
type Rep DimensionValueRequest Source # 
type Rep DimensionValueRequest = D1 (MetaData "DimensionValueRequest" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DimensionValueRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dvrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_dvrEndDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date')))) ((:*:) (S1 (MetaSel (Just Symbol "_dvrFilters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DimensionFilter]))) ((:*:) (S1 (MetaSel (Just Symbol "_dvrStartDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date'))) (S1 (MetaSel (Just Symbol "_dvrDimensionName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

dimensionValueRequest :: DimensionValueRequest Source #

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

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

dvrKind :: Lens' DimensionValueRequest Text Source #

The kind of request this is, in this case dfareporting#dimensionValueRequest.

dvrEndDate :: Lens' DimensionValueRequest (Maybe Day) Source #

The end date of the date range for which to retrieve dimension values. A string of the format "yyyy-MM-dd".

dvrFilters :: Lens' DimensionValueRequest [DimensionFilter] Source #

The list of filters by which to filter values. The filters are ANDed.

dvrStartDate :: Lens' DimensionValueRequest (Maybe Day) Source #

The start date of the date range for which to retrieve dimension values. A string of the format "yyyy-MM-dd".

dvrDimensionName :: Lens' DimensionValueRequest (Maybe Text) Source #

The name of the dimension for which values should be requested.

EventTagsListEventTagTypes

data EventTagsListEventTagTypes Source #

Select only event tags with the specified event tag types. Event tag types can be used to specify whether to use a third-party pixel, a third-party JavaScript URL, or a third-party click-through URL for either impression or click tracking.

Constructors

ClickThroughEventTag
CLICK_THROUGH_EVENT_TAG
ImpressionImageEventTag
IMPRESSION_IMAGE_EVENT_TAG
ImpressionJavascriptEventTag
IMPRESSION_JAVASCRIPT_EVENT_TAG

Instances

Enum EventTagsListEventTagTypes Source # 
Eq EventTagsListEventTagTypes Source # 
Data EventTagsListEventTagTypes Source # 

Methods

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

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

toConstr :: EventTagsListEventTagTypes -> Constr #

dataTypeOf :: EventTagsListEventTagTypes -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EventTagsListEventTagTypes Source # 
Read EventTagsListEventTagTypes Source # 
Show EventTagsListEventTagTypes Source # 
Generic EventTagsListEventTagTypes Source # 
Hashable EventTagsListEventTagTypes Source # 
ToJSON EventTagsListEventTagTypes Source # 
FromJSON EventTagsListEventTagTypes Source # 
FromHttpApiData EventTagsListEventTagTypes Source # 
ToHttpApiData EventTagsListEventTagTypes Source # 
type Rep EventTagsListEventTagTypes Source # 
type Rep EventTagsListEventTagTypes = D1 (MetaData "EventTagsListEventTagTypes" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ClickThroughEventTag" PrefixI False) U1) ((:+:) (C1 (MetaCons "ImpressionImageEventTag" PrefixI False) U1) (C1 (MetaCons "ImpressionJavascriptEventTag" PrefixI False) U1)))

FloodlightConfigurationsListResponse

data FloodlightConfigurationsListResponse Source #

Floodlight Configuration List Response

See: floodlightConfigurationsListResponse smart constructor.

Instances

Eq FloodlightConfigurationsListResponse Source # 
Data FloodlightConfigurationsListResponse Source # 

Methods

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

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

toConstr :: FloodlightConfigurationsListResponse -> Constr #

dataTypeOf :: FloodlightConfigurationsListResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FloodlightConfigurationsListResponse Source # 
Generic FloodlightConfigurationsListResponse Source # 
ToJSON FloodlightConfigurationsListResponse Source # 
FromJSON FloodlightConfigurationsListResponse Source # 
type Rep FloodlightConfigurationsListResponse Source # 
type Rep FloodlightConfigurationsListResponse = D1 (MetaData "FloodlightConfigurationsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FloodlightConfigurationsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fclrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_fclrFloodlightConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [FloodlightConfiguration])))))

floodlightConfigurationsListResponse :: FloodlightConfigurationsListResponse Source #

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

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

fclrKind :: Lens' FloodlightConfigurationsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#floodlightConfigurationsListResponse".

FloodlightActivitiesListResponse

data FloodlightActivitiesListResponse Source #

Floodlight Activity List Response

See: floodlightActivitiesListResponse smart constructor.

Instances

Eq FloodlightActivitiesListResponse Source # 
Data FloodlightActivitiesListResponse Source # 

Methods

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

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

toConstr :: FloodlightActivitiesListResponse -> Constr #

dataTypeOf :: FloodlightActivitiesListResponse -> DataType #

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

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

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

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

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

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivitiesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivitiesListResponse -> m FloodlightActivitiesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivitiesListResponse -> m FloodlightActivitiesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivitiesListResponse -> m FloodlightActivitiesListResponse #

Show FloodlightActivitiesListResponse Source # 
Generic FloodlightActivitiesListResponse Source # 
ToJSON FloodlightActivitiesListResponse Source # 
FromJSON FloodlightActivitiesListResponse Source # 
type Rep FloodlightActivitiesListResponse Source # 
type Rep FloodlightActivitiesListResponse = D1 (MetaData "FloodlightActivitiesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FloodlightActivitiesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_falrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_falrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_falrFloodlightActivities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [FloodlightActivity]))))))

floodlightActivitiesListResponse :: FloodlightActivitiesListResponse Source #

Creates a value of FloodlightActivitiesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

falrNextPageToken :: Lens' FloodlightActivitiesListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

falrKind :: Lens' FloodlightActivitiesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#floodlightActivitiesListResponse".

FileStatus

data FileStatus Source #

The status of the report file.

Constructors

Cancelled
CANCELLED
Failed
FAILED
Processing
PROCESSING
ReportAvailable
REPORT_AVAILABLE

Instances

Enum FileStatus Source # 
Eq FileStatus Source # 
Data FileStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FileStatus -> c FileStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FileStatus #

toConstr :: FileStatus -> Constr #

dataTypeOf :: FileStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FileStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FileStatus) #

gmapT :: (forall b. Data b => b -> b) -> FileStatus -> FileStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FileStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FileStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> FileStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FileStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FileStatus -> m FileStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FileStatus -> m FileStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FileStatus -> m FileStatus #

Ord FileStatus Source # 
Read FileStatus Source # 
Show FileStatus Source # 
Generic FileStatus Source # 

Associated Types

type Rep FileStatus :: * -> * #

Hashable FileStatus Source # 
ToJSON FileStatus Source # 
FromJSON FileStatus Source # 
FromHttpApiData FileStatus Source # 
ToHttpApiData FileStatus Source # 
type Rep FileStatus Source # 
type Rep FileStatus = D1 (MetaData "FileStatus" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "Cancelled" PrefixI False) U1) (C1 (MetaCons "Failed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Processing" PrefixI False) U1) (C1 (MetaCons "ReportAvailable" PrefixI False) U1)))

CreativeCustomEventArtworkType

data CreativeCustomEventArtworkType Source #

Artwork type used by the creative.This is a read-only field.

Constructors

ArtworkTypeFlash
ARTWORK_TYPE_FLASH
ArtworkTypeHTML5
ARTWORK_TYPE_HTML5
ArtworkTypeImage
ARTWORK_TYPE_IMAGE
ArtworkTypeMixed
ARTWORK_TYPE_MIXED

Instances

Enum CreativeCustomEventArtworkType Source # 
Eq CreativeCustomEventArtworkType Source # 
Data CreativeCustomEventArtworkType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeCustomEventArtworkType -> c CreativeCustomEventArtworkType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeCustomEventArtworkType #

toConstr :: CreativeCustomEventArtworkType -> Constr #

dataTypeOf :: CreativeCustomEventArtworkType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeCustomEventArtworkType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeCustomEventArtworkType) #

gmapT :: (forall b. Data b => b -> b) -> CreativeCustomEventArtworkType -> CreativeCustomEventArtworkType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeCustomEventArtworkType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeCustomEventArtworkType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeCustomEventArtworkType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeCustomEventArtworkType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeCustomEventArtworkType -> m CreativeCustomEventArtworkType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeCustomEventArtworkType -> m CreativeCustomEventArtworkType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeCustomEventArtworkType -> m CreativeCustomEventArtworkType #

Ord CreativeCustomEventArtworkType Source # 
Read CreativeCustomEventArtworkType Source # 
Show CreativeCustomEventArtworkType Source # 
Generic CreativeCustomEventArtworkType Source # 
Hashable CreativeCustomEventArtworkType Source # 
ToJSON CreativeCustomEventArtworkType Source # 
FromJSON CreativeCustomEventArtworkType Source # 
FromHttpApiData CreativeCustomEventArtworkType Source # 
ToHttpApiData CreativeCustomEventArtworkType Source # 
type Rep CreativeCustomEventArtworkType Source # 
type Rep CreativeCustomEventArtworkType = D1 (MetaData "CreativeCustomEventArtworkType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "ArtworkTypeFlash" PrefixI False) U1) (C1 (MetaCons "ArtworkTypeHTML5" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ArtworkTypeImage" PrefixI False) U1) (C1 (MetaCons "ArtworkTypeMixed" PrefixI False) U1)))

CreativeFieldAssignment

data CreativeFieldAssignment Source #

Creative Field Assignment.

See: creativeFieldAssignment smart constructor.

Instances

Eq CreativeFieldAssignment Source # 
Data CreativeFieldAssignment Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeFieldAssignment -> c CreativeFieldAssignment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeFieldAssignment #

toConstr :: CreativeFieldAssignment -> Constr #

dataTypeOf :: CreativeFieldAssignment -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeFieldAssignment) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeFieldAssignment) #

gmapT :: (forall b. Data b => b -> b) -> CreativeFieldAssignment -> CreativeFieldAssignment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeFieldAssignment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeFieldAssignment -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeFieldAssignment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeFieldAssignment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeFieldAssignment -> m CreativeFieldAssignment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeFieldAssignment -> m CreativeFieldAssignment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeFieldAssignment -> m CreativeFieldAssignment #

Show CreativeFieldAssignment Source # 
Generic CreativeFieldAssignment Source # 
ToJSON CreativeFieldAssignment Source # 
FromJSON CreativeFieldAssignment Source # 
type Rep CreativeFieldAssignment Source # 
type Rep CreativeFieldAssignment = D1 (MetaData "CreativeFieldAssignment" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeFieldAssignment'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cfaCreativeFieldId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_cfaCreativeFieldValueId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))

creativeFieldAssignment :: CreativeFieldAssignment Source #

Creates a value of CreativeFieldAssignment with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

AdvertiserGroup

data AdvertiserGroup Source #

Groups advertisers together so that reports can be generated for the entire group at once.

See: advertiserGroup smart constructor.

Instances

Eq AdvertiserGroup Source # 
Data AdvertiserGroup Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdvertiserGroup -> c AdvertiserGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdvertiserGroup #

toConstr :: AdvertiserGroup -> Constr #

dataTypeOf :: AdvertiserGroup -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdvertiserGroup) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdvertiserGroup) #

gmapT :: (forall b. Data b => b -> b) -> AdvertiserGroup -> AdvertiserGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdvertiserGroup -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdvertiserGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdvertiserGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdvertiserGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdvertiserGroup -> m AdvertiserGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertiserGroup -> m AdvertiserGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertiserGroup -> m AdvertiserGroup #

Show AdvertiserGroup Source # 
Generic AdvertiserGroup Source # 
ToJSON AdvertiserGroup Source # 
FromJSON AdvertiserGroup Source # 
type Rep AdvertiserGroup Source # 
type Rep AdvertiserGroup = D1 (MetaData "AdvertiserGroup" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AdvertiserGroup'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_agKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_agAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_agName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_agId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

advertiserGroup :: AdvertiserGroup Source #

Creates a value of AdvertiserGroup with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

agKind :: Lens' AdvertiserGroup Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#advertiserGroup".

agAccountId :: Lens' AdvertiserGroup (Maybe Int64) Source #

Account ID of this advertiser group. This is a read-only field that can be left blank.

agName :: Lens' AdvertiserGroup (Maybe Text) Source #

Name of this advertiser group. This is a required field and must be less than 256 characters long and unique among advertiser groups of the same account.

agId :: Lens' AdvertiserGroup (Maybe Int64) Source #

ID of this advertiser group. This is a read-only, auto-generated field.

TagData

data TagData Source #

Placement Tag Data

See: tagData smart constructor.

Instances

Eq TagData Source # 

Methods

(==) :: TagData -> TagData -> Bool #

(/=) :: TagData -> TagData -> Bool #

Data TagData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TagData -> c TagData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TagData #

toConstr :: TagData -> Constr #

dataTypeOf :: TagData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TagData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TagData) #

gmapT :: (forall b. Data b => b -> b) -> TagData -> TagData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TagData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TagData -> r #

gmapQ :: (forall d. Data d => d -> u) -> TagData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TagData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TagData -> m TagData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TagData -> m TagData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TagData -> m TagData #

Show TagData Source # 
Generic TagData Source # 

Associated Types

type Rep TagData :: * -> * #

Methods

from :: TagData -> Rep TagData x #

to :: Rep TagData x -> TagData #

ToJSON TagData Source # 
FromJSON TagData Source # 
type Rep TagData Source # 
type Rep TagData = D1 (MetaData "TagData" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "TagData'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_tdClickTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tdFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TagDataFormat)))) ((:*:) (S1 (MetaSel (Just Symbol "_tdCreativeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_tdAdId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_tdImpressionTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

tagData :: TagData Source #

Creates a value of TagData with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tdClickTag :: Lens' TagData (Maybe Text) Source #

Tag string to record a click.

tdFormat :: Lens' TagData (Maybe TagDataFormat) Source #

TagData tag format of this tag.

tdCreativeId :: Lens' TagData (Maybe Int64) Source #

Creative associated with this placement tag.

tdAdId :: Lens' TagData (Maybe Int64) Source #

Ad associated with this placement tag.

tdImpressionTag :: Lens' TagData (Maybe Text) Source #

Tag string for serving an ad.

DayPartTargeting

data DayPartTargeting Source #

Day Part Targeting.

See: dayPartTargeting smart constructor.

Instances

Eq DayPartTargeting Source # 
Data DayPartTargeting Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DayPartTargeting -> c DayPartTargeting #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DayPartTargeting #

toConstr :: DayPartTargeting -> Constr #

dataTypeOf :: DayPartTargeting -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DayPartTargeting) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DayPartTargeting) #

gmapT :: (forall b. Data b => b -> b) -> DayPartTargeting -> DayPartTargeting #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DayPartTargeting -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DayPartTargeting -> r #

gmapQ :: (forall d. Data d => d -> u) -> DayPartTargeting -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DayPartTargeting -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DayPartTargeting -> m DayPartTargeting #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DayPartTargeting -> m DayPartTargeting #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DayPartTargeting -> m DayPartTargeting #

Show DayPartTargeting Source # 
Generic DayPartTargeting Source # 
ToJSON DayPartTargeting Source # 
FromJSON DayPartTargeting Source # 
type Rep DayPartTargeting Source # 
type Rep DayPartTargeting = D1 (MetaData "DayPartTargeting" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DayPartTargeting'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dptDaysOfWeek") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DayPartTargetingDaysOfWeekItem]))) ((:*:) (S1 (MetaSel (Just Symbol "_dptHoursOfDay") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int32]))) (S1 (MetaSel (Just Symbol "_dptUserLocalTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

dayPartTargeting :: DayPartTargeting Source #

Creates a value of DayPartTargeting with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dptDaysOfWeek :: Lens' DayPartTargeting [DayPartTargetingDaysOfWeekItem] Source #

Days of the week when the ad will serve. Acceptable values are: - "SUNDAY" - "MONDAY" - "TUESDAY" - "WEDNESDAY" - "THURSDAY" - "FRIDAY" - "SATURDAY"

dptHoursOfDay :: Lens' DayPartTargeting [Int32] Source #

Hours of the day when the ad will serve. Must be an integer between 0 and 23 (inclusive), where 0 is midnight to 1 AM, and 23 is 11 PM to midnight. Can be specified with days of week, in which case the ad would serve during these hours on the specified days. For example, if Monday, Wednesday, Friday are the days of week specified and 9-10am, 3-5pm (hours 9, 15, and 16) is specified, the ad would serve Monday, Wednesdays, and Fridays at 9-10am and 3-5pm.

dptUserLocalTime :: Lens' DayPartTargeting (Maybe Bool) Source #

Whether or not to use the user's local time. If false, the America/New York time zone applies.

CreativeOptimizationConfiguration

data CreativeOptimizationConfiguration Source #

Creative optimization settings.

See: creativeOptimizationConfiguration smart constructor.

Instances

Eq CreativeOptimizationConfiguration Source # 
Data CreativeOptimizationConfiguration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeOptimizationConfiguration -> c CreativeOptimizationConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeOptimizationConfiguration #

toConstr :: CreativeOptimizationConfiguration -> Constr #

dataTypeOf :: CreativeOptimizationConfiguration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeOptimizationConfiguration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeOptimizationConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> CreativeOptimizationConfiguration -> CreativeOptimizationConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeOptimizationConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeOptimizationConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeOptimizationConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeOptimizationConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeOptimizationConfiguration -> m CreativeOptimizationConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeOptimizationConfiguration -> m CreativeOptimizationConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeOptimizationConfiguration -> m CreativeOptimizationConfiguration #

Show CreativeOptimizationConfiguration Source # 
Generic CreativeOptimizationConfiguration Source # 
ToJSON CreativeOptimizationConfiguration Source # 
FromJSON CreativeOptimizationConfiguration Source # 
type Rep CreativeOptimizationConfiguration Source # 
type Rep CreativeOptimizationConfiguration = D1 (MetaData "CreativeOptimizationConfiguration" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeOptimizationConfiguration'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cocOptimizationModel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeOptimizationConfigurationOptimizationModel))) (S1 (MetaSel (Just Symbol "_cocName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cocOptimizationActivitys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [OptimizationActivity]))) (S1 (MetaSel (Just Symbol "_cocId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

creativeOptimizationConfiguration :: CreativeOptimizationConfiguration Source #

Creates a value of CreativeOptimizationConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cocName :: Lens' CreativeOptimizationConfiguration (Maybe Text) Source #

Name of this creative optimization config. This is a required field and must be less than 129 characters long.

cocOptimizationActivitys :: Lens' CreativeOptimizationConfiguration [OptimizationActivity] Source #

List of optimization activities associated with this configuration.

cocId :: Lens' CreativeOptimizationConfiguration (Maybe Int64) Source #

ID of this creative optimization config. This field is auto-generated when the campaign is inserted or updated. It can be null for existing campaigns.

ReportCriteria

data ReportCriteria Source #

The report criteria for a report of type "STANDARD".

See: reportCriteria smart constructor.

Instances

Eq ReportCriteria Source # 
Data ReportCriteria Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportCriteria -> c ReportCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportCriteria #

toConstr :: ReportCriteria -> Constr #

dataTypeOf :: ReportCriteria -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportCriteria) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportCriteria) #

gmapT :: (forall b. Data b => b -> b) -> ReportCriteria -> ReportCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportCriteria -> m ReportCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportCriteria -> m ReportCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportCriteria -> m ReportCriteria #

Show ReportCriteria Source # 
Generic ReportCriteria Source # 

Associated Types

type Rep ReportCriteria :: * -> * #

ToJSON ReportCriteria Source # 
FromJSON ReportCriteria Source # 
type Rep ReportCriteria Source # 
type Rep ReportCriteria = D1 (MetaData "ReportCriteria" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ReportCriteria'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcMetricNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) ((:*:) (S1 (MetaSel (Just Symbol "_rcCustomRichMediaEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CustomRichMediaEvents))) (S1 (MetaSel (Just Symbol "_rcDimensionFilters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DimensionValue]))))) ((:*:) (S1 (MetaSel (Just Symbol "_rcActivities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Activities))) ((:*:) (S1 (MetaSel (Just Symbol "_rcDateRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateRange))) (S1 (MetaSel (Just Symbol "_rcDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SortedDimension])))))))

reportCriteria :: ReportCriteria Source #

Creates a value of ReportCriteria with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rcMetricNames :: Lens' ReportCriteria [Text] Source #

The list of names of metrics the report should include.

rcDimensionFilters :: Lens' ReportCriteria [DimensionValue] Source #

The list of filters on which dimensions are filtered. Filters for different dimensions are ANDed, filters for the same dimension are grouped together and ORed.

rcDateRange :: Lens' ReportCriteria (Maybe DateRange) Source #

The date range for which this report should be run.

rcDimensions :: Lens' ReportCriteria [SortedDimension] Source #

The list of standard dimensions the report should include.

FloodlightConfigurationNATuralSearchConversionAttributionOption

data FloodlightConfigurationNATuralSearchConversionAttributionOption Source #

Types of attribution options for natural search conversions.

Constructors

ExcludeNATuralSearchConversionAttribution
EXCLUDE_NATURAL_SEARCH_CONVERSION_ATTRIBUTION
IncludeNATuralSearchConversionAttribution
INCLUDE_NATURAL_SEARCH_CONVERSION_ATTRIBUTION
IncludeNATuralSearchTieredConversionAttribution
INCLUDE_NATURAL_SEARCH_TIERED_CONVERSION_ATTRIBUTION

Instances

Enum FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 
Eq FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 
Data FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightConfigurationNATuralSearchConversionAttributionOption -> c FloodlightConfigurationNATuralSearchConversionAttributionOption #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightConfigurationNATuralSearchConversionAttributionOption #

toConstr :: FloodlightConfigurationNATuralSearchConversionAttributionOption -> Constr #

dataTypeOf :: FloodlightConfigurationNATuralSearchConversionAttributionOption -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightConfigurationNATuralSearchConversionAttributionOption) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightConfigurationNATuralSearchConversionAttributionOption) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightConfigurationNATuralSearchConversionAttributionOption -> FloodlightConfigurationNATuralSearchConversionAttributionOption #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightConfigurationNATuralSearchConversionAttributionOption -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightConfigurationNATuralSearchConversionAttributionOption -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightConfigurationNATuralSearchConversionAttributionOption -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightConfigurationNATuralSearchConversionAttributionOption -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightConfigurationNATuralSearchConversionAttributionOption -> m FloodlightConfigurationNATuralSearchConversionAttributionOption #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightConfigurationNATuralSearchConversionAttributionOption -> m FloodlightConfigurationNATuralSearchConversionAttributionOption #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightConfigurationNATuralSearchConversionAttributionOption -> m FloodlightConfigurationNATuralSearchConversionAttributionOption #

Ord FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 
Read FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 
Show FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 
Generic FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 
Hashable FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 
ToJSON FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 
FromJSON FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 
FromHttpApiData FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 
ToHttpApiData FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 
type Rep FloodlightConfigurationNATuralSearchConversionAttributionOption Source # 
type Rep FloodlightConfigurationNATuralSearchConversionAttributionOption = D1 (MetaData "FloodlightConfigurationNATuralSearchConversionAttributionOption" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ExcludeNATuralSearchConversionAttribution" PrefixI False) U1) ((:+:) (C1 (MetaCons "IncludeNATuralSearchConversionAttribution" PrefixI False) U1) (C1 (MetaCons "IncludeNATuralSearchTieredConversionAttribution" PrefixI False) U1)))

PlacementStrategiesListResponse

data PlacementStrategiesListResponse Source #

Placement Strategy List Response

See: placementStrategiesListResponse smart constructor.

Instances

Eq PlacementStrategiesListResponse Source # 
Data PlacementStrategiesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementStrategiesListResponse -> c PlacementStrategiesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementStrategiesListResponse #

toConstr :: PlacementStrategiesListResponse -> Constr #

dataTypeOf :: PlacementStrategiesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementStrategiesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementStrategiesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> PlacementStrategiesListResponse -> PlacementStrategiesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementStrategiesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementStrategiesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementStrategiesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementStrategiesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementStrategiesListResponse -> m PlacementStrategiesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementStrategiesListResponse -> m PlacementStrategiesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementStrategiesListResponse -> m PlacementStrategiesListResponse #

Show PlacementStrategiesListResponse Source # 
Generic PlacementStrategiesListResponse Source # 
ToJSON PlacementStrategiesListResponse Source # 
FromJSON PlacementStrategiesListResponse Source # 
type Rep PlacementStrategiesListResponse Source # 
type Rep PlacementStrategiesListResponse = D1 (MetaData "PlacementStrategiesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PlacementStrategiesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pslrPlacementStrategies") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PlacementStrategy]))) ((:*:) (S1 (MetaSel (Just Symbol "_pslrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pslrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

placementStrategiesListResponse :: PlacementStrategiesListResponse Source #

Creates a value of PlacementStrategiesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pslrNextPageToken :: Lens' PlacementStrategiesListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

pslrKind :: Lens' PlacementStrategiesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#placementStrategiesListResponse".

CreativeAssetArtworkType

data CreativeAssetArtworkType Source #

Artwork type of rich media creative. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA.

Constructors

CAATArtworkTypeFlash
ARTWORK_TYPE_FLASH
CAATArtworkTypeHTML5
ARTWORK_TYPE_HTML5
CAATArtworkTypeImage
ARTWORK_TYPE_IMAGE
CAATArtworkTypeMixed
ARTWORK_TYPE_MIXED

Instances

Enum CreativeAssetArtworkType Source # 
Eq CreativeAssetArtworkType Source # 
Data CreativeAssetArtworkType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetArtworkType -> c CreativeAssetArtworkType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetArtworkType #

toConstr :: CreativeAssetArtworkType -> Constr #

dataTypeOf :: CreativeAssetArtworkType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetArtworkType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetArtworkType) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetArtworkType -> CreativeAssetArtworkType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetArtworkType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetArtworkType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetArtworkType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetArtworkType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetArtworkType -> m CreativeAssetArtworkType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetArtworkType -> m CreativeAssetArtworkType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetArtworkType -> m CreativeAssetArtworkType #

Ord CreativeAssetArtworkType Source # 
Read CreativeAssetArtworkType Source # 
Show CreativeAssetArtworkType Source # 
Generic CreativeAssetArtworkType Source # 
Hashable CreativeAssetArtworkType Source # 
ToJSON CreativeAssetArtworkType Source # 
FromJSON CreativeAssetArtworkType Source # 
FromHttpApiData CreativeAssetArtworkType Source # 
ToHttpApiData CreativeAssetArtworkType Source # 
type Rep CreativeAssetArtworkType Source # 
type Rep CreativeAssetArtworkType = D1 (MetaData "CreativeAssetArtworkType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "CAATArtworkTypeFlash" PrefixI False) U1) (C1 (MetaCons "CAATArtworkTypeHTML5" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CAATArtworkTypeImage" PrefixI False) U1) (C1 (MetaCons "CAATArtworkTypeMixed" PrefixI False) U1)))

SubAccount

data SubAccount Source #

Contains properties of a DCM subaccount.

See: subAccount smart constructor.

Instances

Eq SubAccount Source # 
Data SubAccount Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SubAccount -> c SubAccount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SubAccount #

toConstr :: SubAccount -> Constr #

dataTypeOf :: SubAccount -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SubAccount) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SubAccount) #

gmapT :: (forall b. Data b => b -> b) -> SubAccount -> SubAccount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SubAccount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SubAccount -> r #

gmapQ :: (forall d. Data d => d -> u) -> SubAccount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SubAccount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SubAccount -> m SubAccount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SubAccount -> m SubAccount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SubAccount -> m SubAccount #

Show SubAccount Source # 
Generic SubAccount Source # 

Associated Types

type Rep SubAccount :: * -> * #

ToJSON SubAccount Source # 
FromJSON SubAccount Source # 
type Rep SubAccount Source # 
type Rep SubAccount = D1 (MetaData "SubAccount" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "SubAccount'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_saKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_saAvailablePermissionIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64])))) ((:*:) (S1 (MetaSel (Just Symbol "_saAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_saName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_saId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))))

subAccount :: SubAccount Source #

Creates a value of SubAccount with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

saKind :: Lens' SubAccount Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#subaccount".

saAvailablePermissionIds :: Lens' SubAccount [Int64] Source #

IDs of the available user role permissions for this subaccount.

saAccountId :: Lens' SubAccount (Maybe Int64) Source #

ID of the account that contains this subaccount. This is a read-only field that can be left blank.

saName :: Lens' SubAccount (Maybe Text) Source #

Name of this subaccount. This is a required field. Must be less than 128 characters long and be unique among subaccounts of the same account.

saId :: Lens' SubAccount (Maybe Int64) Source #

ID of this subaccount. This is a read-only, auto-generated field.

InventoryItemsListResponse

data InventoryItemsListResponse Source #

Inventory item List Response

See: inventoryItemsListResponse smart constructor.

Instances

Eq InventoryItemsListResponse Source # 
Data InventoryItemsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InventoryItemsListResponse -> c InventoryItemsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InventoryItemsListResponse #

toConstr :: InventoryItemsListResponse -> Constr #

dataTypeOf :: InventoryItemsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InventoryItemsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InventoryItemsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> InventoryItemsListResponse -> InventoryItemsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InventoryItemsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InventoryItemsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> InventoryItemsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InventoryItemsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InventoryItemsListResponse -> m InventoryItemsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryItemsListResponse -> m InventoryItemsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryItemsListResponse -> m InventoryItemsListResponse #

Show InventoryItemsListResponse Source # 
Generic InventoryItemsListResponse Source # 
ToJSON InventoryItemsListResponse Source # 
FromJSON InventoryItemsListResponse Source # 
type Rep InventoryItemsListResponse Source # 
type Rep InventoryItemsListResponse = D1 (MetaData "InventoryItemsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "InventoryItemsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_iilrInventoryItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [InventoryItem]))) ((:*:) (S1 (MetaSel (Just Symbol "_iilrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_iilrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

inventoryItemsListResponse :: InventoryItemsListResponse Source #

Creates a value of InventoryItemsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

iilrNextPageToken :: Lens' InventoryItemsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

iilrKind :: Lens' InventoryItemsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#inventoryItemsListResponse".

CustomFloodlightVariableType

data CustomFloodlightVariableType Source #

The type of custom floodlight variable to supply a value for. These map to the "u[1-20]=" in the tags.

Constructors

U1
U1
U10
U10
U11
U11
U12
U12
U13
U13
U14
U14
U15
U15
U16
U16
U17
U17
U18
U18
U19
U19
U2
U2
U20
U20
U3
U3
U4
U4
U5
U5
U6
U6
U7
U7
U8
U8
U9
U9

Instances

Enum CustomFloodlightVariableType Source # 
Eq CustomFloodlightVariableType Source # 
Data CustomFloodlightVariableType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CustomFloodlightVariableType -> c CustomFloodlightVariableType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CustomFloodlightVariableType #

toConstr :: CustomFloodlightVariableType -> Constr #

dataTypeOf :: CustomFloodlightVariableType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CustomFloodlightVariableType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CustomFloodlightVariableType) #

gmapT :: (forall b. Data b => b -> b) -> CustomFloodlightVariableType -> CustomFloodlightVariableType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CustomFloodlightVariableType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CustomFloodlightVariableType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CustomFloodlightVariableType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CustomFloodlightVariableType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CustomFloodlightVariableType -> m CustomFloodlightVariableType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CustomFloodlightVariableType -> m CustomFloodlightVariableType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CustomFloodlightVariableType -> m CustomFloodlightVariableType #

Ord CustomFloodlightVariableType Source # 
Read CustomFloodlightVariableType Source # 
Show CustomFloodlightVariableType Source # 
Generic CustomFloodlightVariableType Source # 
Hashable CustomFloodlightVariableType Source # 
ToJSON CustomFloodlightVariableType Source # 
FromJSON CustomFloodlightVariableType Source # 
FromHttpApiData CustomFloodlightVariableType Source # 
ToHttpApiData CustomFloodlightVariableType Source # 
type Rep CustomFloodlightVariableType Source # 
type Rep CustomFloodlightVariableType = D1 (MetaData "CustomFloodlightVariableType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "U1" PrefixI False) U1) (C1 (MetaCons "U10" PrefixI False) U1)) ((:+:) (C1 (MetaCons "U11" PrefixI False) U1) ((:+:) (C1 (MetaCons "U12" PrefixI False) U1) (C1 (MetaCons "U13" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "U14" PrefixI False) U1) (C1 (MetaCons "U15" PrefixI False) U1)) ((:+:) (C1 (MetaCons "U16" PrefixI False) U1) ((:+:) (C1 (MetaCons "U17" PrefixI False) U1) (C1 (MetaCons "U18" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "U19" PrefixI False) U1) (C1 (MetaCons "U2" PrefixI False) U1)) ((:+:) (C1 (MetaCons "U20" PrefixI False) U1) ((:+:) (C1 (MetaCons "U3" PrefixI False) U1) (C1 (MetaCons "U4" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "U5" PrefixI False) U1) (C1 (MetaCons "U6" PrefixI False) U1)) ((:+:) (C1 (MetaCons "U7" PrefixI False) U1) ((:+:) (C1 (MetaCons "U8" PrefixI False) U1) (C1 (MetaCons "U9" PrefixI False) U1))))))

Ad

data Ad Source #

Contains properties of a DCM ad.

See: ad smart constructor.

Instances

Eq Ad Source # 

Methods

(==) :: Ad -> Ad -> Bool #

(/=) :: Ad -> Ad -> Bool #

Data Ad Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ad -> c Ad #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ad #

toConstr :: Ad -> Constr #

dataTypeOf :: Ad -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Ad) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ad) #

gmapT :: (forall b. Data b => b -> b) -> Ad -> Ad #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ad -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ad -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ad -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ad -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ad -> m Ad #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ad -> m Ad #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ad -> m Ad #

Show Ad Source # 

Methods

showsPrec :: Int -> Ad -> ShowS #

show :: Ad -> String #

showList :: [Ad] -> ShowS #

Generic Ad Source # 

Associated Types

type Rep Ad :: * -> * #

Methods

from :: Ad -> Rep Ad x #

to :: Rep Ad x -> Ad #

ToJSON Ad Source # 
FromJSON Ad Source # 
type Rep Ad Source # 
type Rep Ad = D1 (MetaData "Ad" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Ad'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aCreativeGroupAssignments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeGroupAssignment]))) (S1 (MetaSel (Just Symbol "_aGeoTargeting") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GeoTargeting)))) ((:*:) (S1 (MetaSel (Just Symbol "_aCreativeRotation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeRotation))) (S1 (MetaSel (Just Symbol "_aTechnologyTargeting") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TechnologyTargeting))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aAudienceSegmentId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_aDayPartTargeting") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DayPartTargeting)))) ((:*:) (S1 (MetaSel (Just Symbol "_aSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Size))) ((:*:) (S1 (MetaSel (Just Symbol "_aStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_aKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aClickThroughURLSuffixProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ClickThroughURLSuffixProperties))) (S1 (MetaSel (Just Symbol "_aCampaignIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue)))) ((:*:) (S1 (MetaSel (Just Symbol "_aAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_aAdvertiserIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aSSLCompliant") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_aCampaignId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_aIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) ((:*:) (S1 (MetaSel (Just Symbol "_aClickThroughURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ClickThroughURL))) (S1 (MetaSel (Just Symbol "_aDeliverySchedule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeliverySchedule)))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aEventTagOverrides") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [EventTagOverride]))) (S1 (MetaSel (Just Symbol "_aActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_aAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aKeyValueTargetingExpression") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe KeyValueTargetingExpression))) (S1 (MetaSel (Just Symbol "_aEndTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')))) ((:*:) (S1 (MetaSel (Just Symbol "_aCreateInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo))) ((:*:) (S1 (MetaSel (Just Symbol "_aLastModifiedInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo))) (S1 (MetaSel (Just Symbol "_aId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aSSLRequired") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_aComments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_aSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_aType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AdType))) (S1 (MetaSel (Just Symbol "_aRemarketingListExpression") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ListTargetingExpression)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aDynamicClickTracker") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_aCompatibility") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AdCompatibility)))) ((:*:) (S1 (MetaSel (Just Symbol "_aArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_aDefaultClickThroughEventTagProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DefaultClickThroughEventTagProperties))) (S1 (MetaSel (Just Symbol "_aPlacementAssignments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PlacementAssignment]))))))))))

aCreativeGroupAssignments :: Lens' Ad [CreativeGroupAssignment] Source #

Creative group assignments for this ad. Applicable when type is AD_SERVING_CLICK_TRACKER. Only one assignment per creative group number is allowed for a maximum of two assignments.

aGeoTargeting :: Lens' Ad (Maybe GeoTargeting) Source #

Geographical targeting information for this ad.Applicable when type is AD_SERVING_STANDARD_AD.

aCreativeRotation :: Lens' Ad (Maybe CreativeRotation) Source #

Creative rotation for this ad. Applicable when type is AD_SERVING_DEFAULT_AD, AD_SERVING_STANDARD_AD, or AD_SERVING_TRACKING. When type is AD_SERVING_DEFAULT_AD, this field should have exactly one creativeAssignment.

aTechnologyTargeting :: Lens' Ad (Maybe TechnologyTargeting) Source #

Technology platform targeting information for this ad. Applicable when type is AD_SERVING_STANDARD_AD.

aAudienceSegmentId :: Lens' Ad (Maybe Int64) Source #

Audience segment ID that is being targeted for this ad. Applicable when type is AD_SERVING_STANDARD_AD.

aDayPartTargeting :: Lens' Ad (Maybe DayPartTargeting) Source #

Time and day targeting information for this ad. Applicable when type is AD_SERVING_STANDARD_AD.

aSize :: Lens' Ad (Maybe Size) Source #

Size of this ad. Applicable when type is AD_SERVING_DEFAULT_AD.

aStartTime :: Lens' Ad (Maybe UTCTime) Source #

Date and time that this ad should start serving. If creating an ad, this field must be a time in the future. This is a required field on insertion.

aKind :: Lens' Ad Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#ad".

aClickThroughURLSuffixProperties :: Lens' Ad (Maybe ClickThroughURLSuffixProperties) Source #

Click-through URL suffix properties for this ad. Applies to the URL in the ad or (if overriding ad properties) the URL in the creative.

aCampaignIdDimensionValue :: Lens' Ad (Maybe DimensionValue) Source #

Dimension value for the ID of the campaign. This is a read-only, auto-generated field.

aAdvertiserId :: Lens' Ad (Maybe Int64) Source #

Advertiser ID of this ad. This is a required field on insertion.

aAdvertiserIdDimensionValue :: Lens' Ad (Maybe DimensionValue) Source #

Dimension value for the ID of the advertiser. This is a read-only, auto-generated field.

aSSLCompliant :: Lens' Ad (Maybe Bool) Source #

Whether this ad is ssl compliant. This is a read-only field that is auto-generated when the ad is inserted or updated.

aCampaignId :: Lens' Ad (Maybe Int64) Source #

Campaign ID of this ad. This is a required field on insertion.

aIdDimensionValue :: Lens' Ad (Maybe DimensionValue) Source #

Dimension value for the ID of this ad. This is a read-only, auto-generated field.

aClickThroughURL :: Lens' Ad (Maybe ClickThroughURL) Source #

Click-through URL for this ad. This is a required field on insertion. Applicable when type is AD_SERVING_CLICK_TRACKER.

aDeliverySchedule :: Lens' Ad (Maybe DeliverySchedule) Source #

Delivery schedule information for this ad. Applicable when type is AD_SERVING_STANDARD_AD or AD_SERVING_TRACKING. This field along with subfields priority and impressionRatio are required on insertion when type is AD_SERVING_STANDARD_AD.

aEventTagOverrides :: Lens' Ad [EventTagOverride] Source #

Event tag overrides for this ad.

aActive :: Lens' Ad (Maybe Bool) Source #

Whether this ad is active.

aAccountId :: Lens' Ad (Maybe Int64) Source #

Account ID of this ad. This is a read-only field that can be left blank.

aName :: Lens' Ad (Maybe Text) Source #

Name of this ad. This is a required field and must be less than 256 characters long.

aKeyValueTargetingExpression :: Lens' Ad (Maybe KeyValueTargetingExpression) Source #

Key-value targeting information for this ad. Applicable when type is AD_SERVING_STANDARD_AD.

aEndTime :: Lens' Ad (Maybe UTCTime) Source #

Date and time that this ad should stop serving. Must be later than the start time. This is a required field on insertion.

aCreateInfo :: Lens' Ad (Maybe LastModifiedInfo) Source #

Information about the creation of this ad.This is a read-only field.

aLastModifiedInfo :: Lens' Ad (Maybe LastModifiedInfo) Source #

Information about the most recent modification of this ad. This is a read-only field.

aId :: Lens' Ad (Maybe Int64) Source #

ID of this ad. This is a read-only, auto-generated field.

aSSLRequired :: Lens' Ad (Maybe Bool) Source #

Whether this ad requires ssl. This is a read-only field that is auto-generated when the ad is inserted or updated.

aComments :: Lens' Ad (Maybe Text) Source #

Comments for this ad.

aSubAccountId :: Lens' Ad (Maybe Int64) Source #

Subaccount ID of this ad. This is a read-only field that can be left blank.

aType :: Lens' Ad (Maybe AdType) Source #

Type of ad. This is a required field on insertion. Note that default ads (AD_SERVING_DEFAULT_AD) cannot be created directly (see Creative resource).

aRemarketingListExpression :: Lens' Ad (Maybe ListTargetingExpression) Source #

Applicable when type is AD_SERVING_STANDARD_AD. Remarketing list targeting expression for this ad.

aDynamicClickTracker :: Lens' Ad (Maybe Bool) Source #

Whether this ad is a dynamic click tracker. Applicable when type is AD_SERVING_CLICK_TRACKER. This is a required field on insert, and is read-only after insert.

aCompatibility :: Lens' Ad (Maybe AdCompatibility) Source #

Compatibility of this ad. Applicable when type is AD_SERVING_DEFAULT_AD. DISPLAY and DISPLAY_INTERSTITIAL refer to either rendering on desktop or on mobile devices or in mobile apps for regular or interstitial ads, respectively. APP and APP_INTERSTITIAL are only used for existing default ads. New mobile placements must be assigned DISPLAY or DISPLAY_INTERSTITIAL and default ads created for those placements will be limited to those compatibility types. IN_STREAM_VIDEO refers to rendering in-stream video ads developed with the VAST standard.

aArchived :: Lens' Ad (Maybe Bool) Source #

Whether this ad is archived.

aDefaultClickThroughEventTagProperties :: Lens' Ad (Maybe DefaultClickThroughEventTagProperties) Source #

Default click-through event tag properties for this ad.

aPlacementAssignments :: Lens' Ad [PlacementAssignment] Source #

Placement assignments for this ad.

ConversionErrorCode

data ConversionErrorCode Source #

The error code.

Constructors

Internal
INTERNAL
InvalidArgument
INVALID_ARGUMENT
NotFound
NOT_FOUND
PermissionDenied
PERMISSION_DENIED

Instances

Enum ConversionErrorCode Source # 
Eq ConversionErrorCode Source # 
Data ConversionErrorCode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConversionErrorCode -> c ConversionErrorCode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConversionErrorCode #

toConstr :: ConversionErrorCode -> Constr #

dataTypeOf :: ConversionErrorCode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConversionErrorCode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConversionErrorCode) #

gmapT :: (forall b. Data b => b -> b) -> ConversionErrorCode -> ConversionErrorCode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConversionErrorCode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConversionErrorCode -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConversionErrorCode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConversionErrorCode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConversionErrorCode -> m ConversionErrorCode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConversionErrorCode -> m ConversionErrorCode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConversionErrorCode -> m ConversionErrorCode #

Ord ConversionErrorCode Source # 
Read ConversionErrorCode Source # 
Show ConversionErrorCode Source # 
Generic ConversionErrorCode Source # 
Hashable ConversionErrorCode Source # 
ToJSON ConversionErrorCode Source # 
FromJSON ConversionErrorCode Source # 
FromHttpApiData ConversionErrorCode Source # 
ToHttpApiData ConversionErrorCode Source # 
type Rep ConversionErrorCode Source # 
type Rep ConversionErrorCode = D1 (MetaData "ConversionErrorCode" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "Internal" PrefixI False) U1) (C1 (MetaCons "InvalidArgument" PrefixI False) U1)) ((:+:) (C1 (MetaCons "NotFound" PrefixI False) U1) (C1 (MetaCons "PermissionDenied" PrefixI False) U1)))

FloodlightActivitiesListSortOrder

data FloodlightActivitiesListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

FALSOAscending
ASCENDING
FALSODescending
DESCENDING

Instances

Enum FloodlightActivitiesListSortOrder Source # 
Eq FloodlightActivitiesListSortOrder Source # 
Data FloodlightActivitiesListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivitiesListSortOrder -> c FloodlightActivitiesListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivitiesListSortOrder #

toConstr :: FloodlightActivitiesListSortOrder -> Constr #

dataTypeOf :: FloodlightActivitiesListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivitiesListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivitiesListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivitiesListSortOrder -> FloodlightActivitiesListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivitiesListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivitiesListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivitiesListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivitiesListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivitiesListSortOrder -> m FloodlightActivitiesListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivitiesListSortOrder -> m FloodlightActivitiesListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivitiesListSortOrder -> m FloodlightActivitiesListSortOrder #

Ord FloodlightActivitiesListSortOrder Source # 
Read FloodlightActivitiesListSortOrder Source # 
Show FloodlightActivitiesListSortOrder Source # 
Generic FloodlightActivitiesListSortOrder Source # 
Hashable FloodlightActivitiesListSortOrder Source # 
ToJSON FloodlightActivitiesListSortOrder Source # 
FromJSON FloodlightActivitiesListSortOrder Source # 
FromHttpApiData FloodlightActivitiesListSortOrder Source # 
ToHttpApiData FloodlightActivitiesListSortOrder Source # 
type Rep FloodlightActivitiesListSortOrder Source # 
type Rep FloodlightActivitiesListSortOrder = D1 (MetaData "FloodlightActivitiesListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "FALSOAscending" PrefixI False) U1) (C1 (MetaCons "FALSODescending" PrefixI False) U1))

Project

data Project Source #

Contains properties of a DoubleClick Planning project.

See: project smart constructor.

Instances

Eq Project Source # 

Methods

(==) :: Project -> Project -> Bool #

(/=) :: Project -> Project -> Bool #

Data Project Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Project -> c Project #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Project #

toConstr :: Project -> Constr #

dataTypeOf :: Project -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Project) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Project) #

gmapT :: (forall b. Data b => b -> b) -> Project -> Project #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Project -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Project -> r #

gmapQ :: (forall d. Data d => d -> u) -> Project -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Project -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Project -> m Project #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Project -> m Project #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Project -> m Project #

Show Project Source # 
Generic Project Source # 

Associated Types

type Rep Project :: * -> * #

Methods

from :: Project -> Rep Project x #

to :: Rep Project x -> Project #

ToJSON Project Source # 
FromJSON Project Source # 
type Rep Project Source # 
type Rep Project = D1 (MetaData "Project" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Project'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pTargetClicks") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_pClientBillingCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_pTargetCpmNanos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_pTargetConversions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_pBudget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_pAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_pEndDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date'))) ((:*:) (S1 (MetaSel (Just Symbol "_pOverview") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pTargetImpressions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pStartDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date'))) (S1 (MetaSel (Just Symbol "_pTargetCpcNanos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_pAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_pName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pLastModifiedInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_pAudienceAgeGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProjectAudienceAgeGroup))) (S1 (MetaSel (Just Symbol "_pSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) (S1 (MetaSel (Just Symbol "_pAudienceGender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProjectAudienceGender))) ((:*:) (S1 (MetaSel (Just Symbol "_pClientName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pTargetCpaNanos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))))))

pTargetClicks :: Lens' Project (Maybe Int64) Source #

Number of clicks that the advertiser is targeting.

pClientBillingCode :: Lens' Project (Maybe Text) Source #

Client billing code of this project.

pTargetCpmNanos :: Lens' Project (Maybe Int64) Source #

CPM that the advertiser is targeting.

pTargetConversions :: Lens' Project (Maybe Int64) Source #

Number of conversions that the advertiser is targeting.

pBudget :: Lens' Project (Maybe Int64) Source #

Budget of this project in the currency specified by the current account. The value stored in this field represents only the non-fractional amount. For example, for USD, the smallest value that can be represented by this field is 1 US dollar.

pKind :: Lens' Project Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#project".

pAdvertiserId :: Lens' Project (Maybe Int64) Source #

Advertiser ID of this project.

pEndDate :: Lens' Project (Maybe Day) Source #

End date of the project.

pOverview :: Lens' Project (Maybe Text) Source #

Overview of this project.

pTargetImpressions :: Lens' Project (Maybe Int64) Source #

Number of impressions that the advertiser is targeting.

pStartDate :: Lens' Project (Maybe Day) Source #

Start date of the project.

pTargetCpcNanos :: Lens' Project (Maybe Int64) Source #

CPC that the advertiser is targeting.

pAccountId :: Lens' Project (Maybe Int64) Source #

Account ID of this project.

pName :: Lens' Project (Maybe Text) Source #

Name of this project.

pLastModifiedInfo :: Lens' Project (Maybe LastModifiedInfo) Source #

Information about the most recent modification of this project.

pId :: Lens' Project (Maybe Int64) Source #

ID of this project. This is a read-only, auto-generated field.

pAudienceAgeGroup :: Lens' Project (Maybe ProjectAudienceAgeGroup) Source #

Audience age group of this project.

pSubAccountId :: Lens' Project (Maybe Int64) Source #

Subaccount ID of this project.

pAudienceGender :: Lens' Project (Maybe ProjectAudienceGender) Source #

Audience gender of this project.

pClientName :: Lens' Project (Maybe Text) Source #

Name of the project client.

pTargetCpaNanos :: Lens' Project (Maybe Int64) Source #

CPA that the advertiser is targeting.

FileFormat

data FileFormat Source #

The output format of the report. Only available once the file is available.

Constructors

CSV
CSV
Excel
EXCEL

Instances

Enum FileFormat Source # 
Eq FileFormat Source # 
Data FileFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FileFormat -> c FileFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FileFormat #

toConstr :: FileFormat -> Constr #

dataTypeOf :: FileFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FileFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FileFormat) #

gmapT :: (forall b. Data b => b -> b) -> FileFormat -> FileFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FileFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FileFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> FileFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FileFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FileFormat -> m FileFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FileFormat -> m FileFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FileFormat -> m FileFormat #

Ord FileFormat Source # 
Read FileFormat Source # 
Show FileFormat Source # 
Generic FileFormat Source # 

Associated Types

type Rep FileFormat :: * -> * #

Hashable FileFormat Source # 
ToJSON FileFormat Source # 
FromJSON FileFormat Source # 
FromHttpApiData FileFormat Source # 
ToHttpApiData FileFormat Source # 
type Rep FileFormat Source # 
type Rep FileFormat = D1 (MetaData "FileFormat" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CSV" PrefixI False) U1) (C1 (MetaCons "Excel" PrefixI False) U1))

EncryptionInfoEncryptionEntityType

data EncryptionInfoEncryptionEntityType Source #

The encryption entity type. This should match the encryption configuration for ad serving or Data Transfer.

Constructors

AdwordsCustomer
ADWORDS_CUSTOMER
DBmAdvertiser
DBM_ADVERTISER
DBmPartner
DBM_PARTNER
DcmAccount
DCM_ACCOUNT
DcmAdvertiser
DCM_ADVERTISER
EncryptionEntityTypeUnknown
ENCRYPTION_ENTITY_TYPE_UNKNOWN

Instances

Enum EncryptionInfoEncryptionEntityType Source # 
Eq EncryptionInfoEncryptionEntityType Source # 
Data EncryptionInfoEncryptionEntityType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EncryptionInfoEncryptionEntityType -> c EncryptionInfoEncryptionEntityType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EncryptionInfoEncryptionEntityType #

toConstr :: EncryptionInfoEncryptionEntityType -> Constr #

dataTypeOf :: EncryptionInfoEncryptionEntityType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EncryptionInfoEncryptionEntityType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EncryptionInfoEncryptionEntityType) #

gmapT :: (forall b. Data b => b -> b) -> EncryptionInfoEncryptionEntityType -> EncryptionInfoEncryptionEntityType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EncryptionInfoEncryptionEntityType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EncryptionInfoEncryptionEntityType -> r #

gmapQ :: (forall d. Data d => d -> u) -> EncryptionInfoEncryptionEntityType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EncryptionInfoEncryptionEntityType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EncryptionInfoEncryptionEntityType -> m EncryptionInfoEncryptionEntityType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EncryptionInfoEncryptionEntityType -> m EncryptionInfoEncryptionEntityType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EncryptionInfoEncryptionEntityType -> m EncryptionInfoEncryptionEntityType #

Ord EncryptionInfoEncryptionEntityType Source # 
Read EncryptionInfoEncryptionEntityType Source # 
Show EncryptionInfoEncryptionEntityType Source # 
Generic EncryptionInfoEncryptionEntityType Source # 
Hashable EncryptionInfoEncryptionEntityType Source # 
ToJSON EncryptionInfoEncryptionEntityType Source # 
FromJSON EncryptionInfoEncryptionEntityType Source # 
FromHttpApiData EncryptionInfoEncryptionEntityType Source # 
ToHttpApiData EncryptionInfoEncryptionEntityType Source # 
type Rep EncryptionInfoEncryptionEntityType Source # 
type Rep EncryptionInfoEncryptionEntityType = D1 (MetaData "EncryptionInfoEncryptionEntityType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "AdwordsCustomer" PrefixI False) U1) ((:+:) (C1 (MetaCons "DBmAdvertiser" PrefixI False) U1) (C1 (MetaCons "DBmPartner" PrefixI False) U1))) ((:+:) (C1 (MetaCons "DcmAccount" PrefixI False) U1) ((:+:) (C1 (MetaCons "DcmAdvertiser" PrefixI False) U1) (C1 (MetaCons "EncryptionEntityTypeUnknown" PrefixI False) U1))))

PricingSchedulePricingType

data PricingSchedulePricingType Source #

Placement pricing type. This field is required on insertion.

Constructors

PricingTypeCpa
PRICING_TYPE_CPA
PricingTypeCpc
PRICING_TYPE_CPC
PricingTypeCpm
PRICING_TYPE_CPM
PricingTypeFlatRateClicks
PRICING_TYPE_FLAT_RATE_CLICKS
PricingTypeFlatRateImpressions
PRICING_TYPE_FLAT_RATE_IMPRESSIONS

Instances

Enum PricingSchedulePricingType Source # 
Eq PricingSchedulePricingType Source # 
Data PricingSchedulePricingType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PricingSchedulePricingType -> c PricingSchedulePricingType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PricingSchedulePricingType #

toConstr :: PricingSchedulePricingType -> Constr #

dataTypeOf :: PricingSchedulePricingType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PricingSchedulePricingType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PricingSchedulePricingType) #

gmapT :: (forall b. Data b => b -> b) -> PricingSchedulePricingType -> PricingSchedulePricingType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PricingSchedulePricingType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PricingSchedulePricingType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PricingSchedulePricingType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PricingSchedulePricingType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PricingSchedulePricingType -> m PricingSchedulePricingType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PricingSchedulePricingType -> m PricingSchedulePricingType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PricingSchedulePricingType -> m PricingSchedulePricingType #

Ord PricingSchedulePricingType Source # 
Read PricingSchedulePricingType Source # 
Show PricingSchedulePricingType Source # 
Generic PricingSchedulePricingType Source # 
Hashable PricingSchedulePricingType Source # 
ToJSON PricingSchedulePricingType Source # 
FromJSON PricingSchedulePricingType Source # 
FromHttpApiData PricingSchedulePricingType Source # 
ToHttpApiData PricingSchedulePricingType Source # 
type Rep PricingSchedulePricingType Source # 
type Rep PricingSchedulePricingType = D1 (MetaData "PricingSchedulePricingType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "PricingTypeCpa" PrefixI False) U1) (C1 (MetaCons "PricingTypeCpc" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PricingTypeCpm" PrefixI False) U1) ((:+:) (C1 (MetaCons "PricingTypeFlatRateClicks" PrefixI False) U1) (C1 (MetaCons "PricingTypeFlatRateImpressions" PrefixI False) U1))))

ReportFloodlightCriteria

data ReportFloodlightCriteria Source #

The report criteria for a report of type "FLOODLIGHT".

See: reportFloodlightCriteria smart constructor.

Instances

Eq ReportFloodlightCriteria Source # 
Data ReportFloodlightCriteria Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportFloodlightCriteria -> c ReportFloodlightCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportFloodlightCriteria #

toConstr :: ReportFloodlightCriteria -> Constr #

dataTypeOf :: ReportFloodlightCriteria -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportFloodlightCriteria) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportFloodlightCriteria) #

gmapT :: (forall b. Data b => b -> b) -> ReportFloodlightCriteria -> ReportFloodlightCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportFloodlightCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportFloodlightCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportFloodlightCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportFloodlightCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportFloodlightCriteria -> m ReportFloodlightCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportFloodlightCriteria -> m ReportFloodlightCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportFloodlightCriteria -> m ReportFloodlightCriteria #

Show ReportFloodlightCriteria Source # 
Generic ReportFloodlightCriteria Source # 
ToJSON ReportFloodlightCriteria Source # 
FromJSON ReportFloodlightCriteria Source # 
type Rep ReportFloodlightCriteria Source # 
type Rep ReportFloodlightCriteria = D1 (MetaData "ReportFloodlightCriteria" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ReportFloodlightCriteria'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rfcReportProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportFloodlightCriteriaReportProperties))) ((:*:) (S1 (MetaSel (Just Symbol "_rfcMetricNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_rfcCustomRichMediaEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DimensionValue]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rfcDimensionFilters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DimensionValue]))) (S1 (MetaSel (Just Symbol "_rfcDateRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateRange)))) ((:*:) (S1 (MetaSel (Just Symbol "_rfcFloodlightConfigId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_rfcDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SortedDimension])))))))

reportFloodlightCriteria :: ReportFloodlightCriteria Source #

Creates a value of ReportFloodlightCriteria with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rfcMetricNames :: Lens' ReportFloodlightCriteria [Text] Source #

The list of names of metrics the report should include.

rfcCustomRichMediaEvents :: Lens' ReportFloodlightCriteria [DimensionValue] Source #

The list of custom rich media events to include.

rfcDimensionFilters :: Lens' ReportFloodlightCriteria [DimensionValue] Source #

The list of filters on which dimensions are filtered. Filters for different dimensions are ANDed, filters for the same dimension are grouped together and ORed.

rfcDateRange :: Lens' ReportFloodlightCriteria (Maybe DateRange) Source #

The date range this report should be run for.

rfcFloodlightConfigId :: Lens' ReportFloodlightCriteria (Maybe DimensionValue) Source #

The floodlight ID for which to show data in this report. All advertisers associated with that ID will automatically be added. The dimension of the value needs to be 'dfa:floodlightConfigId'.

rfcDimensions :: Lens' ReportFloodlightCriteria [SortedDimension] Source #

The list of dimensions the report should include.

CreativeCustomEventTargetType

data CreativeCustomEventTargetType Source #

Target type used by the event.

Constructors

TargetBlank
TARGET_BLANK
TargetParent
TARGET_PARENT
TargetPopup
TARGET_POPUP
TargetSelf
TARGET_SELF
TargetTop
TARGET_TOP

Instances

Enum CreativeCustomEventTargetType Source # 
Eq CreativeCustomEventTargetType Source # 
Data CreativeCustomEventTargetType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeCustomEventTargetType -> c CreativeCustomEventTargetType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeCustomEventTargetType #

toConstr :: CreativeCustomEventTargetType -> Constr #

dataTypeOf :: CreativeCustomEventTargetType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeCustomEventTargetType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeCustomEventTargetType) #

gmapT :: (forall b. Data b => b -> b) -> CreativeCustomEventTargetType -> CreativeCustomEventTargetType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeCustomEventTargetType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeCustomEventTargetType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeCustomEventTargetType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeCustomEventTargetType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeCustomEventTargetType -> m CreativeCustomEventTargetType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeCustomEventTargetType -> m CreativeCustomEventTargetType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeCustomEventTargetType -> m CreativeCustomEventTargetType #

Ord CreativeCustomEventTargetType Source # 
Read CreativeCustomEventTargetType Source # 
Show CreativeCustomEventTargetType Source # 
Generic CreativeCustomEventTargetType Source # 
Hashable CreativeCustomEventTargetType Source # 
ToJSON CreativeCustomEventTargetType Source # 
FromJSON CreativeCustomEventTargetType Source # 
FromHttpApiData CreativeCustomEventTargetType Source # 
ToHttpApiData CreativeCustomEventTargetType Source # 
type Rep CreativeCustomEventTargetType Source # 
type Rep CreativeCustomEventTargetType = D1 (MetaData "CreativeCustomEventTargetType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "TargetBlank" PrefixI False) U1) (C1 (MetaCons "TargetParent" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TargetPopup" PrefixI False) U1) ((:+:) (C1 (MetaCons "TargetSelf" PrefixI False) U1) (C1 (MetaCons "TargetTop" PrefixI False) U1))))

ReportsListScope

data ReportsListScope Source #

The scope that defines which results are returned, default is 'MINE'.

Constructors

All

ALL All reports in account.

Mine

MINE My reports.

Instances

Enum ReportsListScope Source # 
Eq ReportsListScope Source # 
Data ReportsListScope Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportsListScope -> c ReportsListScope #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportsListScope #

toConstr :: ReportsListScope -> Constr #

dataTypeOf :: ReportsListScope -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportsListScope) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportsListScope) #

gmapT :: (forall b. Data b => b -> b) -> ReportsListScope -> ReportsListScope #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportsListScope -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportsListScope -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportsListScope -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportsListScope -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportsListScope -> m ReportsListScope #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportsListScope -> m ReportsListScope #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportsListScope -> m ReportsListScope #

Ord ReportsListScope Source # 
Read ReportsListScope Source # 
Show ReportsListScope Source # 
Generic ReportsListScope Source # 
Hashable ReportsListScope Source # 
ToJSON ReportsListScope Source # 
FromJSON ReportsListScope Source # 
FromHttpApiData ReportsListScope Source # 
ToHttpApiData ReportsListScope Source # 
type Rep ReportsListScope Source # 
type Rep ReportsListScope = D1 (MetaData "ReportsListScope" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "All" PrefixI False) U1) (C1 (MetaCons "Mine" PrefixI False) U1))

Size

data Size Source #

Represents the dimensions of ads, placements, creatives, or creative assets.

See: size smart constructor.

Instances

Eq Size Source # 

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Data Size Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Size -> c Size #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Size #

toConstr :: Size -> Constr #

dataTypeOf :: Size -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Size) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Size) #

gmapT :: (forall b. Data b => b -> b) -> Size -> Size #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Size -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Size -> r #

gmapQ :: (forall d. Data d => d -> u) -> Size -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Size -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Size -> m Size #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Size -> m Size #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Size -> m Size #

Show Size Source # 

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Generic Size Source # 

Associated Types

type Rep Size :: * -> * #

Methods

from :: Size -> Rep Size x #

to :: Rep Size x -> Size #

ToJSON Size Source # 
FromJSON Size Source # 
type Rep Size Source # 

size :: Size Source #

Creates a value of Size with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sHeight :: Lens' Size (Maybe Int32) Source #

Height of this size.

sKind :: Lens' Size Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#size".

sWidth :: Lens' Size (Maybe Int32) Source #

Width of this size.

sIab :: Lens' Size (Maybe Bool) Source #

IAB standard size. This is a read-only, auto-generated field.

sId :: Lens' Size (Maybe Int64) Source #

ID of this size. This is a read-only, auto-generated field.

CreativeAssetDurationType

data CreativeAssetDurationType Source #

Duration type for which an asset will be displayed. Applicable to the following creative types: all RICH_MEDIA.

Constructors

AssetDurationTypeAuto
ASSET_DURATION_TYPE_AUTO
AssetDurationTypeCustom
ASSET_DURATION_TYPE_CUSTOM
AssetDurationTypeNone
ASSET_DURATION_TYPE_NONE

Instances

Enum CreativeAssetDurationType Source # 
Eq CreativeAssetDurationType Source # 
Data CreativeAssetDurationType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetDurationType -> c CreativeAssetDurationType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetDurationType #

toConstr :: CreativeAssetDurationType -> Constr #

dataTypeOf :: CreativeAssetDurationType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetDurationType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetDurationType) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetDurationType -> CreativeAssetDurationType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetDurationType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetDurationType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetDurationType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetDurationType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetDurationType -> m CreativeAssetDurationType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetDurationType -> m CreativeAssetDurationType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetDurationType -> m CreativeAssetDurationType #

Ord CreativeAssetDurationType Source # 
Read CreativeAssetDurationType Source # 
Show CreativeAssetDurationType Source # 
Generic CreativeAssetDurationType Source # 
Hashable CreativeAssetDurationType Source # 
ToJSON CreativeAssetDurationType Source # 
FromJSON CreativeAssetDurationType Source # 
FromHttpApiData CreativeAssetDurationType Source # 
ToHttpApiData CreativeAssetDurationType Source # 
type Rep CreativeAssetDurationType Source # 
type Rep CreativeAssetDurationType = D1 (MetaData "CreativeAssetDurationType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "AssetDurationTypeAuto" PrefixI False) U1) ((:+:) (C1 (MetaCons "AssetDurationTypeCustom" PrefixI False) U1) (C1 (MetaCons "AssetDurationTypeNone" PrefixI False) U1)))

TargetableRemarketingListListSource

data TargetableRemarketingListListSource Source #

Product from which this targetable remarketing list was originated.

Constructors

RemarketingListSourceAdx
REMARKETING_LIST_SOURCE_ADX
RemarketingListSourceDBm
REMARKETING_LIST_SOURCE_DBM
RemarketingListSourceDfa
REMARKETING_LIST_SOURCE_DFA
RemarketingListSourceDfp
REMARKETING_LIST_SOURCE_DFP
RemarketingListSourceDmp
REMARKETING_LIST_SOURCE_DMP
RemarketingListSourceGa
REMARKETING_LIST_SOURCE_GA
RemarketingListSourceGplus
REMARKETING_LIST_SOURCE_GPLUS
RemarketingListSourceOther
REMARKETING_LIST_SOURCE_OTHER
RemarketingListSourcePlayStore
REMARKETING_LIST_SOURCE_PLAY_STORE
RemarketingListSourceXfp
REMARKETING_LIST_SOURCE_XFP
RemarketingListSourceYouTube
REMARKETING_LIST_SOURCE_YOUTUBE

Instances

Enum TargetableRemarketingListListSource Source # 
Eq TargetableRemarketingListListSource Source # 
Data TargetableRemarketingListListSource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TargetableRemarketingListListSource -> c TargetableRemarketingListListSource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TargetableRemarketingListListSource #

toConstr :: TargetableRemarketingListListSource -> Constr #

dataTypeOf :: TargetableRemarketingListListSource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TargetableRemarketingListListSource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TargetableRemarketingListListSource) #

gmapT :: (forall b. Data b => b -> b) -> TargetableRemarketingListListSource -> TargetableRemarketingListListSource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TargetableRemarketingListListSource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TargetableRemarketingListListSource -> r #

gmapQ :: (forall d. Data d => d -> u) -> TargetableRemarketingListListSource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TargetableRemarketingListListSource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TargetableRemarketingListListSource -> m TargetableRemarketingListListSource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetableRemarketingListListSource -> m TargetableRemarketingListListSource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetableRemarketingListListSource -> m TargetableRemarketingListListSource #

Ord TargetableRemarketingListListSource Source # 
Read TargetableRemarketingListListSource Source # 
Show TargetableRemarketingListListSource Source # 
Generic TargetableRemarketingListListSource Source # 
Hashable TargetableRemarketingListListSource Source # 
ToJSON TargetableRemarketingListListSource Source # 
FromJSON TargetableRemarketingListListSource Source # 
FromHttpApiData TargetableRemarketingListListSource Source # 
ToHttpApiData TargetableRemarketingListListSource Source # 
type Rep TargetableRemarketingListListSource Source # 
type Rep TargetableRemarketingListListSource = D1 (MetaData "TargetableRemarketingListListSource" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "RemarketingListSourceAdx" PrefixI False) U1) (C1 (MetaCons "RemarketingListSourceDBm" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RemarketingListSourceDfa" PrefixI False) U1) ((:+:) (C1 (MetaCons "RemarketingListSourceDfp" PrefixI False) U1) (C1 (MetaCons "RemarketingListSourceDmp" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "RemarketingListSourceGa" PrefixI False) U1) ((:+:) (C1 (MetaCons "RemarketingListSourceGplus" PrefixI False) U1) (C1 (MetaCons "RemarketingListSourceOther" PrefixI False) U1))) ((:+:) (C1 (MetaCons "RemarketingListSourcePlayStore" PrefixI False) U1) ((:+:) (C1 (MetaCons "RemarketingListSourceXfp" PrefixI False) U1) (C1 (MetaCons "RemarketingListSourceYouTube" PrefixI False) U1)))))

ObjectFilter

data ObjectFilter Source #

Object Filter.

See: objectFilter smart constructor.

Instances

Eq ObjectFilter Source # 
Data ObjectFilter Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjectFilter -> c ObjectFilter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjectFilter #

toConstr :: ObjectFilter -> Constr #

dataTypeOf :: ObjectFilter -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ObjectFilter) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjectFilter) #

gmapT :: (forall b. Data b => b -> b) -> ObjectFilter -> ObjectFilter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjectFilter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjectFilter -> r #

gmapQ :: (forall d. Data d => d -> u) -> ObjectFilter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjectFilter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjectFilter -> m ObjectFilter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectFilter -> m ObjectFilter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectFilter -> m ObjectFilter #

Show ObjectFilter Source # 
Generic ObjectFilter Source # 

Associated Types

type Rep ObjectFilter :: * -> * #

ToJSON ObjectFilter Source # 
FromJSON ObjectFilter Source # 
type Rep ObjectFilter Source # 
type Rep ObjectFilter = D1 (MetaData "ObjectFilter" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ObjectFilter'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ofStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectFilterStatus))) ((:*:) (S1 (MetaSel (Just Symbol "_ofKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_ofObjectIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64]))))))

objectFilter :: ObjectFilter Source #

Creates a value of ObjectFilter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ofStatus :: Lens' ObjectFilter (Maybe ObjectFilterStatus) Source #

Status of the filter. NONE means the user has access to none of the objects. ALL means the user has access to all objects. ASSIGNED means the user has access to the objects with IDs in the objectIds list.

ofKind :: Lens' ObjectFilter Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#objectFilter".

ofObjectIds :: Lens' ObjectFilter [Int64] Source #

Applicable when status is ASSIGNED. The user has access to objects with these object IDs.

CreativeGroupsListSortField

data CreativeGroupsListSortField Source #

Field by which to sort the list.

Constructors

CGLSFID
ID
CGLSFName
NAME

Instances

Enum CreativeGroupsListSortField Source # 
Eq CreativeGroupsListSortField Source # 
Data CreativeGroupsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeGroupsListSortField -> c CreativeGroupsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeGroupsListSortField #

toConstr :: CreativeGroupsListSortField -> Constr #

dataTypeOf :: CreativeGroupsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeGroupsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeGroupsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> CreativeGroupsListSortField -> CreativeGroupsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeGroupsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeGroupsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeGroupsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeGroupsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeGroupsListSortField -> m CreativeGroupsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeGroupsListSortField -> m CreativeGroupsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeGroupsListSortField -> m CreativeGroupsListSortField #

Ord CreativeGroupsListSortField Source # 
Read CreativeGroupsListSortField Source # 
Show CreativeGroupsListSortField Source # 
Generic CreativeGroupsListSortField Source # 
Hashable CreativeGroupsListSortField Source # 
ToJSON CreativeGroupsListSortField Source # 
FromJSON CreativeGroupsListSortField Source # 
FromHttpApiData CreativeGroupsListSortField Source # 
ToHttpApiData CreativeGroupsListSortField Source # 
type Rep CreativeGroupsListSortField Source # 
type Rep CreativeGroupsListSortField = D1 (MetaData "CreativeGroupsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CGLSFID" PrefixI False) U1) (C1 (MetaCons "CGLSFName" PrefixI False) U1))

ReportsConfiguration

data ReportsConfiguration Source #

Reporting Configuration

See: reportsConfiguration smart constructor.

Instances

Eq ReportsConfiguration Source # 
Data ReportsConfiguration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportsConfiguration -> c ReportsConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportsConfiguration #

toConstr :: ReportsConfiguration -> Constr #

dataTypeOf :: ReportsConfiguration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportsConfiguration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportsConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> ReportsConfiguration -> ReportsConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportsConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportsConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportsConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportsConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportsConfiguration -> m ReportsConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportsConfiguration -> m ReportsConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportsConfiguration -> m ReportsConfiguration #

Show ReportsConfiguration Source # 
Generic ReportsConfiguration Source # 
ToJSON ReportsConfiguration Source # 
FromJSON ReportsConfiguration Source # 
type Rep ReportsConfiguration Source # 
type Rep ReportsConfiguration = D1 (MetaData "ReportsConfiguration" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ReportsConfiguration'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rcExposureToConversionEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_rcReportGenerationTimeZoneId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_rcLookbackConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LookbackConfiguration))))))

reportsConfiguration :: ReportsConfiguration Source #

Creates a value of ReportsConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rcExposureToConversionEnabled :: Lens' ReportsConfiguration (Maybe Bool) Source #

Whether the exposure to conversion report is enabled. This report shows detailed pathway information on up to 10 of the most recent ad exposures seen by a user before converting.

rcReportGenerationTimeZoneId :: Lens' ReportsConfiguration (Maybe Int64) Source #

Report generation time zone ID of this account. This is a required field that can only be changed by a superuser. Acceptable values are: - "1" for "America/New_York" - "2" for "Europe/London" - "3" for "Europe/Paris" - "4" for "Africa/Johannesburg" - "5" for "Asia/Jerusalem" - "6" for "Asia/Shanghai" - "7" for "Asia/Hong_Kong" - "8" for "Asia/Tokyo" - "9" for "Australia/Sydney" - "10" for "Asia/Dubai" - "11" for "America/Los_Angeles" - "12" for "Pacific/Auckland" - "13" for "America/Sao_Paulo"

rcLookbackConfiguration :: Lens' ReportsConfiguration (Maybe LookbackConfiguration) Source #

Default lookback windows for new advertisers in this account.

PricingSchedule

data PricingSchedule Source #

Pricing Schedule

See: pricingSchedule smart constructor.

Instances

Eq PricingSchedule Source # 
Data PricingSchedule Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PricingSchedule -> c PricingSchedule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PricingSchedule #

toConstr :: PricingSchedule -> Constr #

dataTypeOf :: PricingSchedule -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PricingSchedule) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PricingSchedule) #

gmapT :: (forall b. Data b => b -> b) -> PricingSchedule -> PricingSchedule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PricingSchedule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PricingSchedule -> r #

gmapQ :: (forall d. Data d => d -> u) -> PricingSchedule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PricingSchedule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PricingSchedule -> m PricingSchedule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PricingSchedule -> m PricingSchedule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PricingSchedule -> m PricingSchedule #

Show PricingSchedule Source # 
Generic PricingSchedule Source # 
ToJSON PricingSchedule Source # 
FromJSON PricingSchedule Source # 
type Rep PricingSchedule Source # 

pricingSchedule :: PricingSchedule Source #

Creates a value of PricingSchedule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

psTestingStartDate :: Lens' PricingSchedule (Maybe Day) Source #

Testing start date of this placement. The hours, minutes, and seconds of the start date should not be set, as doing so will result in an error.

psFloodlightActivityId :: Lens' PricingSchedule (Maybe Int64) Source #

Floodlight activity ID associated with this placement. This field should be set when placement pricing type is set to PRICING_TYPE_CPA.

psEndDate :: Lens' PricingSchedule (Maybe Day) Source #

Placement end date. This date must be later than, or the same day as, the placement start date, but not later than the campaign end date. If, for example, you set 6/25/2015 as both the start and end dates, the effective placement date is just that day only, 6/25/2015. The hours, minutes, and seconds of the end date should not be set, as doing so will result in an error. This field is required on insertion.

psDisregardOverdelivery :: Lens' PricingSchedule (Maybe Bool) Source #

Whether cap costs are ignored by ad serving.

psStartDate :: Lens' PricingSchedule (Maybe Day) Source #

Placement start date. This date must be later than, or the same day as, the campaign start date. The hours, minutes, and seconds of the start date should not be set, as doing so will result in an error. This field is required on insertion.

psPricingType :: Lens' PricingSchedule (Maybe PricingSchedulePricingType) Source #

Placement pricing type. This field is required on insertion.

psFlighted :: Lens' PricingSchedule (Maybe Bool) Source #

Whether this placement is flighted. If true, pricing periods will be computed automatically.

PostalCode

data PostalCode Source #

Contains information about a postal code that can be targeted by ads.

See: postalCode smart constructor.

Instances

Eq PostalCode Source # 
Data PostalCode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PostalCode -> c PostalCode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PostalCode #

toConstr :: PostalCode -> Constr #

dataTypeOf :: PostalCode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PostalCode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PostalCode) #

gmapT :: (forall b. Data b => b -> b) -> PostalCode -> PostalCode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PostalCode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PostalCode -> r #

gmapQ :: (forall d. Data d => d -> u) -> PostalCode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PostalCode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PostalCode -> m PostalCode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PostalCode -> m PostalCode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PostalCode -> m PostalCode #

Show PostalCode Source # 
Generic PostalCode Source # 

Associated Types

type Rep PostalCode :: * -> * #

ToJSON PostalCode Source # 
FromJSON PostalCode Source # 
type Rep PostalCode Source # 
type Rep PostalCode = D1 (MetaData "PostalCode" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PostalCode'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pcKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_pcCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_pcCountryCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_pcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pcCountryDartId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))))

postalCode :: PostalCode Source #

Creates a value of PostalCode with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pcKind :: Lens' PostalCode Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#postalCode".

pcCode :: Lens' PostalCode (Maybe Text) Source #

Postal code. This is equivalent to the id field.

pcCountryCode :: Lens' PostalCode (Maybe Text) Source #

Country code of the country to which this postal code belongs.

pcId :: Lens' PostalCode (Maybe Text) Source #

ID of this postal code.

pcCountryDartId :: Lens' PostalCode (Maybe Int64) Source #

DART ID of the country to which this postal code belongs.

AccountPermissionsListResponse

data AccountPermissionsListResponse Source #

Account Permission List Response

See: accountPermissionsListResponse smart constructor.

Instances

Eq AccountPermissionsListResponse Source # 
Data AccountPermissionsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountPermissionsListResponse -> c AccountPermissionsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountPermissionsListResponse #

toConstr :: AccountPermissionsListResponse -> Constr #

dataTypeOf :: AccountPermissionsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountPermissionsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountPermissionsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> AccountPermissionsListResponse -> AccountPermissionsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountPermissionsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountPermissionsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountPermissionsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountPermissionsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountPermissionsListResponse -> m AccountPermissionsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountPermissionsListResponse -> m AccountPermissionsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountPermissionsListResponse -> m AccountPermissionsListResponse #

Show AccountPermissionsListResponse Source # 
Generic AccountPermissionsListResponse Source # 
ToJSON AccountPermissionsListResponse Source # 
FromJSON AccountPermissionsListResponse Source # 
type Rep AccountPermissionsListResponse Source # 
type Rep AccountPermissionsListResponse = D1 (MetaData "AccountPermissionsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AccountPermissionsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_aplrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_aplrAccountPermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AccountPermission])))))

accountPermissionsListResponse :: AccountPermissionsListResponse Source #

Creates a value of AccountPermissionsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

aplrKind :: Lens' AccountPermissionsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#accountPermissionsListResponse".

Country

data Country Source #

Contains information about a country that can be targeted by ads.

See: country smart constructor.

Instances

Eq Country Source # 

Methods

(==) :: Country -> Country -> Bool #

(/=) :: Country -> Country -> Bool #

Data Country Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Country -> c Country #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Country #

toConstr :: Country -> Constr #

dataTypeOf :: Country -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Country) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Country) #

gmapT :: (forall b. Data b => b -> b) -> Country -> Country #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Country -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Country -> r #

gmapQ :: (forall d. Data d => d -> u) -> Country -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Country -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Country -> m Country #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Country -> m Country #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Country -> m Country #

Show Country Source # 
Generic Country Source # 

Associated Types

type Rep Country :: * -> * #

Methods

from :: Country -> Rep Country x #

to :: Rep Country x -> Country #

ToJSON Country Source # 
FromJSON Country Source # 
type Rep Country Source # 
type Rep Country = D1 (MetaData "Country" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Country'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_cName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cCountryCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cDartId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_cSSLEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))))

country :: Country Source #

Creates a value of Country with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cKind :: Lens' Country Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#country".

cName :: Lens' Country (Maybe Text) Source #

Name of this country.

cDartId :: Lens' Country (Maybe Int64) Source #

DART ID of this country. This is the ID used for targeting and generating reports.

cSSLEnabled :: Lens' Country (Maybe Bool) Source #

Whether ad serving supports secure servers in this country.

PlacementsListSortField

data PlacementsListSortField Source #

Field by which to sort the list.

Constructors

PLSFID
ID
PLSFName
NAME

Instances

Enum PlacementsListSortField Source # 
Eq PlacementsListSortField Source # 
Data PlacementsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementsListSortField -> c PlacementsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementsListSortField #

toConstr :: PlacementsListSortField -> Constr #

dataTypeOf :: PlacementsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> PlacementsListSortField -> PlacementsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementsListSortField -> m PlacementsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementsListSortField -> m PlacementsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementsListSortField -> m PlacementsListSortField #

Ord PlacementsListSortField Source # 
Read PlacementsListSortField Source # 
Show PlacementsListSortField Source # 
Generic PlacementsListSortField Source # 
Hashable PlacementsListSortField Source # 
ToJSON PlacementsListSortField Source # 
FromJSON PlacementsListSortField Source # 
FromHttpApiData PlacementsListSortField Source # 
ToHttpApiData PlacementsListSortField Source # 
type Rep PlacementsListSortField Source # 
type Rep PlacementsListSortField = D1 (MetaData "PlacementsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PLSFID" PrefixI False) U1) (C1 (MetaCons "PLSFName" PrefixI False) U1))

CreativeBackupImageFeaturesItem

data CreativeBackupImageFeaturesItem Source #

Constructors

CBIFIApplicationCache
APPLICATION_CACHE
CBIFIAudio
AUDIO
CBIFICanvas
CANVAS
CBIFICanvasText
CANVAS_TEXT
CBIFICssAnimations
CSS_ANIMATIONS
CBIFICssBackgRoundSize
CSS_BACKGROUND_SIZE
CBIFICssBOrderImage
CSS_BORDER_IMAGE
CBIFICssBOrderRadius
CSS_BORDER_RADIUS
CBIFICssBoxShadow
CSS_BOX_SHADOW
CBIFICssColumns
CSS_COLUMNS
CBIFICssFlexBox
CSS_FLEX_BOX
CBIFICssFontFace
CSS_FONT_FACE
CBIFICssGeneratedContent
CSS_GENERATED_CONTENT
CBIFICssGradients
CSS_GRADIENTS
CBIFICssHsla
CSS_HSLA
CBIFICssMultipleBgs
CSS_MULTIPLE_BGS
CBIFICssOpacity
CSS_OPACITY
CBIFICssReflections
CSS_REFLECTIONS
CBIFICssRgba
CSS_RGBA
CBIFICssTextShadow
CSS_TEXT_SHADOW
CBIFICssTransforms
CSS_TRANSFORMS
CBIFICssTRANSFORMS3D
CSS_TRANSFORMS3D
CBIFICssTransitions
CSS_TRANSITIONS
CBIFIDragAndDrop
DRAG_AND_DROP
CBIFIGeoLocation
GEO_LOCATION
CBIFIHashChange
HASH_CHANGE
CBIFIHistory
HISTORY
CBIFIIndexedDB
INDEXED_DB
CBIFIInlineSvg
INLINE_SVG
CBIFIInputAttrAutocomplete
INPUT_ATTR_AUTOCOMPLETE
CBIFIInputAttrAutofocus
INPUT_ATTR_AUTOFOCUS
CBIFIInputAttrList
INPUT_ATTR_LIST
CBIFIInputAttrMax
INPUT_ATTR_MAX
CBIFIInputAttrMin
INPUT_ATTR_MIN
CBIFIInputAttrMultiple
INPUT_ATTR_MULTIPLE
CBIFIInputAttrPattern
INPUT_ATTR_PATTERN
CBIFIInputAttrPlaceholder
INPUT_ATTR_PLACEHOLDER
CBIFIInputAttrRequired
INPUT_ATTR_REQUIRED
CBIFIInputAttrStep
INPUT_ATTR_STEP
CBIFIInputTypeColor
INPUT_TYPE_COLOR
CBIFIInputTypeDate
INPUT_TYPE_DATE
CBIFIInputTypeDatetime
INPUT_TYPE_DATETIME
CBIFIInputTypeDatetimeLocal
INPUT_TYPE_DATETIME_LOCAL
CBIFIInputTypeEmail
INPUT_TYPE_EMAIL
CBIFIInputTypeMonth
INPUT_TYPE_MONTH
CBIFIInputTypeNumber
INPUT_TYPE_NUMBER
CBIFIInputTypeRange
INPUT_TYPE_RANGE
CBIFIInputTypeSearch
INPUT_TYPE_SEARCH
CBIFIInputTypeTel
INPUT_TYPE_TEL
CBIFIInputTypeTime
INPUT_TYPE_TIME
CBIFIInputTypeURL
INPUT_TYPE_URL
CBIFIInputTypeWeek
INPUT_TYPE_WEEK
CBIFILocalStorage
LOCAL_STORAGE
CBIFIPostMessage
POST_MESSAGE
CBIFISessionStorage
SESSION_STORAGE
CBIFISmil
SMIL
CBIFISvgClipPaths
SVG_CLIP_PATHS
CBIFISvgFeImage
SVG_FE_IMAGE
CBIFISvgFilters
SVG_FILTERS
CBIFISvgHref
SVG_HREF
CBIFITouch
TOUCH
CBIFIVideo
VIDEO
CBIFIWebgl
WEBGL
CBIFIWebSockets
WEB_SOCKETS
CBIFIWebSQLDatabase
WEB_SQL_DATABASE
CBIFIWebWorkers
WEB_WORKERS

Instances

Enum CreativeBackupImageFeaturesItem Source # 
Eq CreativeBackupImageFeaturesItem Source # 
Data CreativeBackupImageFeaturesItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeBackupImageFeaturesItem -> c CreativeBackupImageFeaturesItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeBackupImageFeaturesItem #

toConstr :: CreativeBackupImageFeaturesItem -> Constr #

dataTypeOf :: CreativeBackupImageFeaturesItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeBackupImageFeaturesItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeBackupImageFeaturesItem) #

gmapT :: (forall b. Data b => b -> b) -> CreativeBackupImageFeaturesItem -> CreativeBackupImageFeaturesItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeBackupImageFeaturesItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeBackupImageFeaturesItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeBackupImageFeaturesItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeBackupImageFeaturesItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeBackupImageFeaturesItem -> m CreativeBackupImageFeaturesItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeBackupImageFeaturesItem -> m CreativeBackupImageFeaturesItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeBackupImageFeaturesItem -> m CreativeBackupImageFeaturesItem #

Ord CreativeBackupImageFeaturesItem Source # 
Read CreativeBackupImageFeaturesItem Source # 
Show CreativeBackupImageFeaturesItem Source # 
Generic CreativeBackupImageFeaturesItem Source # 
Hashable CreativeBackupImageFeaturesItem Source # 
ToJSON CreativeBackupImageFeaturesItem Source # 
FromJSON CreativeBackupImageFeaturesItem Source # 
FromHttpApiData CreativeBackupImageFeaturesItem Source # 
ToHttpApiData CreativeBackupImageFeaturesItem Source # 
type Rep CreativeBackupImageFeaturesItem Source # 
type Rep CreativeBackupImageFeaturesItem = D1 (MetaData "CreativeBackupImageFeaturesItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CBIFIApplicationCache" PrefixI False) U1) (C1 (MetaCons "CBIFIAudio" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFICanvas" PrefixI False) U1) (C1 (MetaCons "CBIFICanvasText" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CBIFICssAnimations" PrefixI False) U1) (C1 (MetaCons "CBIFICssBackgRoundSize" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFICssBOrderImage" PrefixI False) U1) (C1 (MetaCons "CBIFICssBOrderRadius" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CBIFICssBoxShadow" PrefixI False) U1) (C1 (MetaCons "CBIFICssColumns" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFICssFlexBox" PrefixI False) U1) (C1 (MetaCons "CBIFICssFontFace" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CBIFICssGeneratedContent" PrefixI False) U1) (C1 (MetaCons "CBIFICssGradients" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFICssHsla" PrefixI False) U1) (C1 (MetaCons "CBIFICssMultipleBgs" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CBIFICssOpacity" PrefixI False) U1) (C1 (MetaCons "CBIFICssReflections" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFICssRgba" PrefixI False) U1) (C1 (MetaCons "CBIFICssTextShadow" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CBIFICssTransforms" PrefixI False) U1) (C1 (MetaCons "CBIFICssTRANSFORMS3D" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFICssTransitions" PrefixI False) U1) (C1 (MetaCons "CBIFIDragAndDrop" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CBIFIGeoLocation" PrefixI False) U1) (C1 (MetaCons "CBIFIHashChange" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFIHistory" PrefixI False) U1) (C1 (MetaCons "CBIFIIndexedDB" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CBIFIInlineSvg" PrefixI False) U1) (C1 (MetaCons "CBIFIInputAttrAutocomplete" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFIInputAttrAutofocus" PrefixI False) U1) ((:+:) (C1 (MetaCons "CBIFIInputAttrList" PrefixI False) U1) (C1 (MetaCons "CBIFIInputAttrMax" PrefixI False) U1))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CBIFIInputAttrMin" PrefixI False) U1) (C1 (MetaCons "CBIFIInputAttrMultiple" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFIInputAttrPattern" PrefixI False) U1) (C1 (MetaCons "CBIFIInputAttrPlaceholder" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CBIFIInputAttrRequired" PrefixI False) U1) (C1 (MetaCons "CBIFIInputAttrStep" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFIInputTypeColor" PrefixI False) U1) (C1 (MetaCons "CBIFIInputTypeDate" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CBIFIInputTypeDatetime" PrefixI False) U1) (C1 (MetaCons "CBIFIInputTypeDatetimeLocal" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFIInputTypeEmail" PrefixI False) U1) (C1 (MetaCons "CBIFIInputTypeMonth" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CBIFIInputTypeNumber" PrefixI False) U1) (C1 (MetaCons "CBIFIInputTypeRange" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFIInputTypeSearch" PrefixI False) U1) (C1 (MetaCons "CBIFIInputTypeTel" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CBIFIInputTypeTime" PrefixI False) U1) (C1 (MetaCons "CBIFIInputTypeURL" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFIInputTypeWeek" PrefixI False) U1) (C1 (MetaCons "CBIFILocalStorage" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CBIFIPostMessage" PrefixI False) U1) (C1 (MetaCons "CBIFISessionStorage" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFISmil" PrefixI False) U1) (C1 (MetaCons "CBIFISvgClipPaths" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CBIFISvgFeImage" PrefixI False) U1) (C1 (MetaCons "CBIFISvgFilters" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFISvgHref" PrefixI False) U1) (C1 (MetaCons "CBIFITouch" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CBIFIVideo" PrefixI False) U1) (C1 (MetaCons "CBIFIWebgl" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CBIFIWebSockets" PrefixI False) U1) ((:+:) (C1 (MetaCons "CBIFIWebSQLDatabase" PrefixI False) U1) (C1 (MetaCons "CBIFIWebWorkers" PrefixI False) U1))))))))

OperatingSystemVersionsListResponse

data OperatingSystemVersionsListResponse Source #

Operating System Version List Response

See: operatingSystemVersionsListResponse smart constructor.

Instances

Eq OperatingSystemVersionsListResponse Source # 
Data OperatingSystemVersionsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OperatingSystemVersionsListResponse -> c OperatingSystemVersionsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OperatingSystemVersionsListResponse #

toConstr :: OperatingSystemVersionsListResponse -> Constr #

dataTypeOf :: OperatingSystemVersionsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OperatingSystemVersionsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OperatingSystemVersionsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> OperatingSystemVersionsListResponse -> OperatingSystemVersionsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OperatingSystemVersionsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OperatingSystemVersionsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> OperatingSystemVersionsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OperatingSystemVersionsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OperatingSystemVersionsListResponse -> m OperatingSystemVersionsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OperatingSystemVersionsListResponse -> m OperatingSystemVersionsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OperatingSystemVersionsListResponse -> m OperatingSystemVersionsListResponse #

Show OperatingSystemVersionsListResponse Source # 
Generic OperatingSystemVersionsListResponse Source # 
ToJSON OperatingSystemVersionsListResponse Source # 
FromJSON OperatingSystemVersionsListResponse Source # 
type Rep OperatingSystemVersionsListResponse Source # 
type Rep OperatingSystemVersionsListResponse = D1 (MetaData "OperatingSystemVersionsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "OperatingSystemVersionsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_osvlrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_osvlrOperatingSystemVersions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [OperatingSystemVersion])))))

operatingSystemVersionsListResponse :: OperatingSystemVersionsListResponse Source #

Creates a value of OperatingSystemVersionsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

osvlrKind :: Lens' OperatingSystemVersionsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#operatingSystemVersionsListResponse".

ClickThroughURLSuffixProperties

data ClickThroughURLSuffixProperties Source #

Click Through URL Suffix settings.

See: clickThroughURLSuffixProperties smart constructor.

Instances

Eq ClickThroughURLSuffixProperties Source # 
Data ClickThroughURLSuffixProperties Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClickThroughURLSuffixProperties -> c ClickThroughURLSuffixProperties #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClickThroughURLSuffixProperties #

toConstr :: ClickThroughURLSuffixProperties -> Constr #

dataTypeOf :: ClickThroughURLSuffixProperties -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ClickThroughURLSuffixProperties) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClickThroughURLSuffixProperties) #

gmapT :: (forall b. Data b => b -> b) -> ClickThroughURLSuffixProperties -> ClickThroughURLSuffixProperties #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClickThroughURLSuffixProperties -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClickThroughURLSuffixProperties -> r #

gmapQ :: (forall d. Data d => d -> u) -> ClickThroughURLSuffixProperties -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClickThroughURLSuffixProperties -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClickThroughURLSuffixProperties -> m ClickThroughURLSuffixProperties #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClickThroughURLSuffixProperties -> m ClickThroughURLSuffixProperties #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClickThroughURLSuffixProperties -> m ClickThroughURLSuffixProperties #

Show ClickThroughURLSuffixProperties Source # 
Generic ClickThroughURLSuffixProperties Source # 
ToJSON ClickThroughURLSuffixProperties Source # 
FromJSON ClickThroughURLSuffixProperties Source # 
type Rep ClickThroughURLSuffixProperties Source # 
type Rep ClickThroughURLSuffixProperties = D1 (MetaData "ClickThroughURLSuffixProperties" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ClickThroughURLSuffixProperties'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ctuspOverrideInheritedSuffix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_ctuspClickThroughURLSuffix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

clickThroughURLSuffixProperties :: ClickThroughURLSuffixProperties Source #

Creates a value of ClickThroughURLSuffixProperties with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ctuspOverrideInheritedSuffix :: Lens' ClickThroughURLSuffixProperties (Maybe Bool) Source #

Whether this entity should override the inherited click-through URL suffix with its own defined value.

ctuspClickThroughURLSuffix :: Lens' ClickThroughURLSuffixProperties (Maybe Text) Source #

Click-through URL suffix to apply to all ads in this entity's scope. Must be less than 128 characters long.

AdvertisersListSortOrder

data AdvertisersListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

ALSOAscending
ASCENDING
ALSODescending
DESCENDING

Instances

Enum AdvertisersListSortOrder Source # 
Eq AdvertisersListSortOrder Source # 
Data AdvertisersListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdvertisersListSortOrder -> c AdvertisersListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdvertisersListSortOrder #

toConstr :: AdvertisersListSortOrder -> Constr #

dataTypeOf :: AdvertisersListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdvertisersListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdvertisersListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> AdvertisersListSortOrder -> AdvertisersListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdvertisersListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdvertisersListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdvertisersListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdvertisersListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdvertisersListSortOrder -> m AdvertisersListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertisersListSortOrder -> m AdvertisersListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertisersListSortOrder -> m AdvertisersListSortOrder #

Ord AdvertisersListSortOrder Source # 
Read AdvertisersListSortOrder Source # 
Show AdvertisersListSortOrder Source # 
Generic AdvertisersListSortOrder Source # 
Hashable AdvertisersListSortOrder Source # 
ToJSON AdvertisersListSortOrder Source # 
FromJSON AdvertisersListSortOrder Source # 
FromHttpApiData AdvertisersListSortOrder Source # 
ToHttpApiData AdvertisersListSortOrder Source # 
type Rep AdvertisersListSortOrder Source # 
type Rep AdvertisersListSortOrder = D1 (MetaData "AdvertisersListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ALSOAscending" PrefixI False) U1) (C1 (MetaCons "ALSODescending" PrefixI False) U1))

CreativeFieldsListSortField

data CreativeFieldsListSortField Source #

Field by which to sort the list.

Constructors

CFLSFID
ID
CFLSFName
NAME

Instances

Enum CreativeFieldsListSortField Source # 
Eq CreativeFieldsListSortField Source # 
Data CreativeFieldsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeFieldsListSortField -> c CreativeFieldsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeFieldsListSortField #

toConstr :: CreativeFieldsListSortField -> Constr #

dataTypeOf :: CreativeFieldsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeFieldsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeFieldsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> CreativeFieldsListSortField -> CreativeFieldsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeFieldsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeFieldsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeFieldsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeFieldsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeFieldsListSortField -> m CreativeFieldsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeFieldsListSortField -> m CreativeFieldsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeFieldsListSortField -> m CreativeFieldsListSortField #

Ord CreativeFieldsListSortField Source # 
Read CreativeFieldsListSortField Source # 
Show CreativeFieldsListSortField Source # 
Generic CreativeFieldsListSortField Source # 
Hashable CreativeFieldsListSortField Source # 
ToJSON CreativeFieldsListSortField Source # 
FromJSON CreativeFieldsListSortField Source # 
FromHttpApiData CreativeFieldsListSortField Source # 
ToHttpApiData CreativeFieldsListSortField Source # 
type Rep CreativeFieldsListSortField Source # 
type Rep CreativeFieldsListSortField = D1 (MetaData "CreativeFieldsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CFLSFID" PrefixI False) U1) (C1 (MetaCons "CFLSFName" PrefixI False) U1))

Pricing

data Pricing Source #

Pricing Information

See: pricing smart constructor.

Instances

Eq Pricing Source # 

Methods

(==) :: Pricing -> Pricing -> Bool #

(/=) :: Pricing -> Pricing -> Bool #

Data Pricing Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pricing -> c Pricing #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pricing #

toConstr :: Pricing -> Constr #

dataTypeOf :: Pricing -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Pricing) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pricing) #

gmapT :: (forall b. Data b => b -> b) -> Pricing -> Pricing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pricing -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pricing -> r #

gmapQ :: (forall d. Data d => d -> u) -> Pricing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pricing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pricing -> m Pricing #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pricing -> m Pricing #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pricing -> m Pricing #

Show Pricing Source # 
Generic Pricing Source # 

Associated Types

type Rep Pricing :: * -> * #

Methods

from :: Pricing -> Rep Pricing x #

to :: Rep Pricing x -> Pricing #

ToJSON Pricing Source # 
FromJSON Pricing Source # 
type Rep Pricing Source # 

pricing :: Pricing Source #

Creates a value of Pricing with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

priEndDate :: Lens' Pricing (Maybe Day) Source #

End date of this inventory item.

priStartDate :: Lens' Pricing (Maybe Day) Source #

Start date of this inventory item.

priGroupType :: Lens' Pricing (Maybe PricingGroupType) Source #

Group type of this inventory item if it represents a placement group. Is null otherwise. There are two type of placement groups: PLANNING_PLACEMENT_GROUP_TYPE_PACKAGE is a simple group of inventory items that acts as a single pricing point for a group of tags. PLANNING_PLACEMENT_GROUP_TYPE_ROADBLOCK is a group of inventory items that not only acts as a single pricing point, but also assumes that all the tags in it will be served at the same time. A roadblock requires one of its assigned inventory items to be marked as primary.

priPricingType :: Lens' Pricing (Maybe PricingPricingType) Source #

Pricing type of this inventory item.

priFlights :: Lens' Pricing [Flight] Source #

Flights of this inventory item. A flight (a.k.a. pricing period) represents the inventory item pricing information for a specific period of time.

priCapCostType :: Lens' Pricing (Maybe PricingCapCostType) Source #

Cap cost type of this inventory item.

AudienceSegmentGroup

data AudienceSegmentGroup Source #

Audience Segment Group.

See: audienceSegmentGroup smart constructor.

Instances

Eq AudienceSegmentGroup Source # 
Data AudienceSegmentGroup Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AudienceSegmentGroup -> c AudienceSegmentGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AudienceSegmentGroup #

toConstr :: AudienceSegmentGroup -> Constr #

dataTypeOf :: AudienceSegmentGroup -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AudienceSegmentGroup) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AudienceSegmentGroup) #

gmapT :: (forall b. Data b => b -> b) -> AudienceSegmentGroup -> AudienceSegmentGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AudienceSegmentGroup -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AudienceSegmentGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> AudienceSegmentGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AudienceSegmentGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AudienceSegmentGroup -> m AudienceSegmentGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AudienceSegmentGroup -> m AudienceSegmentGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AudienceSegmentGroup -> m AudienceSegmentGroup #

Show AudienceSegmentGroup Source # 
Generic AudienceSegmentGroup Source # 
ToJSON AudienceSegmentGroup Source # 
FromJSON AudienceSegmentGroup Source # 
type Rep AudienceSegmentGroup Source # 
type Rep AudienceSegmentGroup = D1 (MetaData "AudienceSegmentGroup" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AudienceSegmentGroup'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_asgAudienceSegments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AudienceSegment]))) ((:*:) (S1 (MetaSel (Just Symbol "_asgName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_asgId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

audienceSegmentGroup :: AudienceSegmentGroup Source #

Creates a value of AudienceSegmentGroup with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

asgAudienceSegments :: Lens' AudienceSegmentGroup [AudienceSegment] Source #

Audience segments assigned to this group. The number of segments must be between 2 and 100.

asgName :: Lens' AudienceSegmentGroup (Maybe Text) Source #

Name of this audience segment group. This is a required field and must be less than 65 characters long.

asgId :: Lens' AudienceSegmentGroup (Maybe Int64) Source #

ID of this audience segment group. This is a read-only, auto-generated field.

OperatingSystem

data OperatingSystem Source #

Contains information about an operating system that can be targeted by ads.

See: operatingSystem smart constructor.

Instances

Eq OperatingSystem Source # 
Data OperatingSystem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OperatingSystem -> c OperatingSystem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OperatingSystem #

toConstr :: OperatingSystem -> Constr #

dataTypeOf :: OperatingSystem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OperatingSystem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OperatingSystem) #

gmapT :: (forall b. Data b => b -> b) -> OperatingSystem -> OperatingSystem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OperatingSystem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OperatingSystem -> r #

gmapQ :: (forall d. Data d => d -> u) -> OperatingSystem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OperatingSystem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OperatingSystem -> m OperatingSystem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OperatingSystem -> m OperatingSystem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OperatingSystem -> m OperatingSystem #

Show OperatingSystem Source # 
Generic OperatingSystem Source # 
ToJSON OperatingSystem Source # 
FromJSON OperatingSystem Source # 
type Rep OperatingSystem Source # 
type Rep OperatingSystem = D1 (MetaData "OperatingSystem" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "OperatingSystem'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_osDesktop") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_osKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_osName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_osMobile") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_osDartId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))))

operatingSystem :: OperatingSystem Source #

Creates a value of OperatingSystem with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

osDesktop :: Lens' OperatingSystem (Maybe Bool) Source #

Whether this operating system is for desktop.

osKind :: Lens' OperatingSystem Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#operatingSystem".

osName :: Lens' OperatingSystem (Maybe Text) Source #

Name of this operating system.

osMobile :: Lens' OperatingSystem (Maybe Bool) Source #

Whether this operating system is for mobile.

osDartId :: Lens' OperatingSystem (Maybe Int64) Source #

DART ID of this operating system. This is the ID used for targeting.

Flight

data Flight Source #

Flight

See: flight smart constructor.

Instances

Eq Flight Source # 

Methods

(==) :: Flight -> Flight -> Bool #

(/=) :: Flight -> Flight -> Bool #

Data Flight Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Flight -> c Flight #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Flight #

toConstr :: Flight -> Constr #

dataTypeOf :: Flight -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Flight) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Flight) #

gmapT :: (forall b. Data b => b -> b) -> Flight -> Flight #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Flight -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Flight -> r #

gmapQ :: (forall d. Data d => d -> u) -> Flight -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Flight -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Flight -> m Flight #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Flight -> m Flight #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Flight -> m Flight #

Show Flight Source # 
Generic Flight Source # 

Associated Types

type Rep Flight :: * -> * #

Methods

from :: Flight -> Rep Flight x #

to :: Rep Flight x -> Flight #

ToJSON Flight Source # 
FromJSON Flight Source # 
type Rep Flight Source # 
type Rep Flight = D1 (MetaData "Flight" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Flight'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_fRateOrCost") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_fEndDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date')))) ((:*:) (S1 (MetaSel (Just Symbol "_fStartDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date'))) (S1 (MetaSel (Just Symbol "_fUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

flight :: Flight Source #

Creates a value of Flight with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

fRateOrCost :: Lens' Flight (Maybe Int64) Source #

Rate or cost of this flight.

fEndDate :: Lens' Flight (Maybe Day) Source #

Inventory item flight end date.

fStartDate :: Lens' Flight (Maybe Day) Source #

Inventory item flight start date.

fUnits :: Lens' Flight (Maybe Int64) Source #

Units of this flight.

UserDefinedVariableConfigurationVariableType

data UserDefinedVariableConfigurationVariableType Source #

Variable name in the tag. This is a required field.

Instances

Enum UserDefinedVariableConfigurationVariableType Source # 
Eq UserDefinedVariableConfigurationVariableType Source # 
Data UserDefinedVariableConfigurationVariableType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserDefinedVariableConfigurationVariableType -> c UserDefinedVariableConfigurationVariableType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserDefinedVariableConfigurationVariableType #

toConstr :: UserDefinedVariableConfigurationVariableType -> Constr #

dataTypeOf :: UserDefinedVariableConfigurationVariableType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserDefinedVariableConfigurationVariableType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserDefinedVariableConfigurationVariableType) #

gmapT :: (forall b. Data b => b -> b) -> UserDefinedVariableConfigurationVariableType -> UserDefinedVariableConfigurationVariableType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserDefinedVariableConfigurationVariableType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserDefinedVariableConfigurationVariableType -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserDefinedVariableConfigurationVariableType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserDefinedVariableConfigurationVariableType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserDefinedVariableConfigurationVariableType -> m UserDefinedVariableConfigurationVariableType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserDefinedVariableConfigurationVariableType -> m UserDefinedVariableConfigurationVariableType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserDefinedVariableConfigurationVariableType -> m UserDefinedVariableConfigurationVariableType #

Ord UserDefinedVariableConfigurationVariableType Source # 
Read UserDefinedVariableConfigurationVariableType Source # 
Show UserDefinedVariableConfigurationVariableType Source # 
Generic UserDefinedVariableConfigurationVariableType Source # 
Hashable UserDefinedVariableConfigurationVariableType Source # 
ToJSON UserDefinedVariableConfigurationVariableType Source # 
FromJSON UserDefinedVariableConfigurationVariableType Source # 
FromHttpApiData UserDefinedVariableConfigurationVariableType Source # 
ToHttpApiData UserDefinedVariableConfigurationVariableType Source # 
type Rep UserDefinedVariableConfigurationVariableType Source # 
type Rep UserDefinedVariableConfigurationVariableType = D1 (MetaData "UserDefinedVariableConfigurationVariableType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UDVCVTU1" PrefixI False) U1) (C1 (MetaCons "UDVCVTU10" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UDVCVTU11" PrefixI False) U1) ((:+:) (C1 (MetaCons "UDVCVTU12" PrefixI False) U1) (C1 (MetaCons "UDVCVTU13" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "UDVCVTU14" PrefixI False) U1) (C1 (MetaCons "UDVCVTU15" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UDVCVTU16" PrefixI False) U1) ((:+:) (C1 (MetaCons "UDVCVTU17" PrefixI False) U1) (C1 (MetaCons "UDVCVTU18" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UDVCVTU19" PrefixI False) U1) (C1 (MetaCons "UDVCVTU2" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UDVCVTU20" PrefixI False) U1) ((:+:) (C1 (MetaCons "UDVCVTU3" PrefixI False) U1) (C1 (MetaCons "UDVCVTU4" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "UDVCVTU5" PrefixI False) U1) (C1 (MetaCons "UDVCVTU6" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UDVCVTU7" PrefixI False) U1) ((:+:) (C1 (MetaCons "UDVCVTU8" PrefixI False) U1) (C1 (MetaCons "UDVCVTU9" PrefixI False) U1))))))

FsCommandPositionOption

data FsCommandPositionOption Source #

Position in the browser where the window will open.

Constructors

Centered
CENTERED
DistanceFromTopLeftCorner
DISTANCE_FROM_TOP_LEFT_CORNER

Instances

Enum FsCommandPositionOption Source # 
Eq FsCommandPositionOption Source # 
Data FsCommandPositionOption Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FsCommandPositionOption -> c FsCommandPositionOption #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FsCommandPositionOption #

toConstr :: FsCommandPositionOption -> Constr #

dataTypeOf :: FsCommandPositionOption -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FsCommandPositionOption) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FsCommandPositionOption) #

gmapT :: (forall b. Data b => b -> b) -> FsCommandPositionOption -> FsCommandPositionOption #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FsCommandPositionOption -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FsCommandPositionOption -> r #

gmapQ :: (forall d. Data d => d -> u) -> FsCommandPositionOption -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FsCommandPositionOption -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FsCommandPositionOption -> m FsCommandPositionOption #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FsCommandPositionOption -> m FsCommandPositionOption #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FsCommandPositionOption -> m FsCommandPositionOption #

Ord FsCommandPositionOption Source # 
Read FsCommandPositionOption Source # 
Show FsCommandPositionOption Source # 
Generic FsCommandPositionOption Source # 
Hashable FsCommandPositionOption Source # 
ToJSON FsCommandPositionOption Source # 
FromJSON FsCommandPositionOption Source # 
FromHttpApiData FsCommandPositionOption Source # 
ToHttpApiData FsCommandPositionOption Source # 
type Rep FsCommandPositionOption Source # 
type Rep FsCommandPositionOption = D1 (MetaData "FsCommandPositionOption" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Centered" PrefixI False) U1) (C1 (MetaCons "DistanceFromTopLeftCorner" PrefixI False) U1))

CitiesListResponse

data CitiesListResponse Source #

City List Response

See: citiesListResponse smart constructor.

Instances

Eq CitiesListResponse Source # 
Data CitiesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CitiesListResponse -> c CitiesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CitiesListResponse #

toConstr :: CitiesListResponse -> Constr #

dataTypeOf :: CitiesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CitiesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CitiesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> CitiesListResponse -> CitiesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CitiesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CitiesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> CitiesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CitiesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CitiesListResponse -> m CitiesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CitiesListResponse -> m CitiesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CitiesListResponse -> m CitiesListResponse #

Show CitiesListResponse Source # 
Generic CitiesListResponse Source # 
ToJSON CitiesListResponse Source # 
FromJSON CitiesListResponse Source # 
type Rep CitiesListResponse Source # 
type Rep CitiesListResponse = D1 (MetaData "CitiesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CitiesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_citKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_citCities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [City])))))

citiesListResponse :: CitiesListResponse Source #

Creates a value of CitiesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

citKind :: Lens' CitiesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#citiesListResponse".

Dimension

data Dimension Source #

Represents a dimension.

See: dimension smart constructor.

Instances

Eq Dimension Source # 
Data Dimension Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dimension -> c Dimension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dimension #

toConstr :: Dimension -> Constr #

dataTypeOf :: Dimension -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Dimension) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dimension) #

gmapT :: (forall b. Data b => b -> b) -> Dimension -> Dimension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dimension -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dimension -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dimension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dimension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dimension -> m Dimension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dimension -> m Dimension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dimension -> m Dimension #

Show Dimension Source # 
Generic Dimension Source # 

Associated Types

type Rep Dimension :: * -> * #

ToJSON Dimension Source # 
FromJSON Dimension Source # 
type Rep Dimension Source # 
type Rep Dimension = D1 (MetaData "Dimension" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Dimension'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_dName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

dimension :: Dimension Source #

Creates a value of Dimension with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dKind :: Lens' Dimension Text Source #

The kind of resource this is, in this case dfareporting#dimension.

dName :: Lens' Dimension (Maybe Text) Source #

The dimension name, e.g. dfa:advertiser

ReportReachCriteria

data ReportReachCriteria Source #

The report criteria for a report of type "REACH".

See: reportReachCriteria smart constructor.

Instances

Eq ReportReachCriteria Source # 
Data ReportReachCriteria Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportReachCriteria -> c ReportReachCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportReachCriteria #

toConstr :: ReportReachCriteria -> Constr #

dataTypeOf :: ReportReachCriteria -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportReachCriteria) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportReachCriteria) #

gmapT :: (forall b. Data b => b -> b) -> ReportReachCriteria -> ReportReachCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportReachCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportReachCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportReachCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportReachCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportReachCriteria -> m ReportReachCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportReachCriteria -> m ReportReachCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportReachCriteria -> m ReportReachCriteria #

Show ReportReachCriteria Source # 
Generic ReportReachCriteria Source # 
ToJSON ReportReachCriteria Source # 
FromJSON ReportReachCriteria Source # 
type Rep ReportReachCriteria Source # 
type Rep ReportReachCriteria = D1 (MetaData "ReportReachCriteria" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ReportReachCriteria'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rrcReachByFrequencyMetricNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_rrcEnableAllDimensionCombinations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_rrcMetricNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_rrcCustomRichMediaEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CustomRichMediaEvents))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rrcDimensionFilters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DimensionValue]))) (S1 (MetaSel (Just Symbol "_rrcActivities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Activities)))) ((:*:) (S1 (MetaSel (Just Symbol "_rrcDateRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateRange))) (S1 (MetaSel (Just Symbol "_rrcDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SortedDimension])))))))

rrcReachByFrequencyMetricNames :: Lens' ReportReachCriteria [Text] Source #

The list of names of Reach By Frequency metrics the report should include.

rrcEnableAllDimensionCombinations :: Lens' ReportReachCriteria (Maybe Bool) Source #

Whether to enable all reach dimension combinations in the report. Defaults to false. If enabled, the date range of the report should be within the last three months.

rrcMetricNames :: Lens' ReportReachCriteria [Text] Source #

The list of names of metrics the report should include.

rrcDimensionFilters :: Lens' ReportReachCriteria [DimensionValue] Source #

The list of filters on which dimensions are filtered. Filters for different dimensions are ANDed, filters for the same dimension are grouped together and ORed.

rrcDateRange :: Lens' ReportReachCriteria (Maybe DateRange) Source #

The date range this report should be run for.

rrcDimensions :: Lens' ReportReachCriteria [SortedDimension] Source #

The list of dimensions the report should include.

CustomRichMediaEvents

data CustomRichMediaEvents Source #

Represents a Custom Rich Media Events group.

See: customRichMediaEvents smart constructor.

Instances

Eq CustomRichMediaEvents Source # 
Data CustomRichMediaEvents Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CustomRichMediaEvents -> c CustomRichMediaEvents #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CustomRichMediaEvents #

toConstr :: CustomRichMediaEvents -> Constr #

dataTypeOf :: CustomRichMediaEvents -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CustomRichMediaEvents) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CustomRichMediaEvents) #

gmapT :: (forall b. Data b => b -> b) -> CustomRichMediaEvents -> CustomRichMediaEvents #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CustomRichMediaEvents -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CustomRichMediaEvents -> r #

gmapQ :: (forall d. Data d => d -> u) -> CustomRichMediaEvents -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CustomRichMediaEvents -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CustomRichMediaEvents -> m CustomRichMediaEvents #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CustomRichMediaEvents -> m CustomRichMediaEvents #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CustomRichMediaEvents -> m CustomRichMediaEvents #

Show CustomRichMediaEvents Source # 
Generic CustomRichMediaEvents Source # 
ToJSON CustomRichMediaEvents Source # 
FromJSON CustomRichMediaEvents Source # 
type Rep CustomRichMediaEvents Source # 
type Rep CustomRichMediaEvents = D1 (MetaData "CustomRichMediaEvents" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CustomRichMediaEvents'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_crmeKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_crmeFilteredEventIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DimensionValue])))))

customRichMediaEvents :: CustomRichMediaEvents Source #

Creates a value of CustomRichMediaEvents with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

crmeKind :: Lens' CustomRichMediaEvents Text Source #

The kind of resource this is, in this case dfareporting#customRichMediaEvents.

crmeFilteredEventIds :: Lens' CustomRichMediaEvents [DimensionValue] Source #

List of custom rich media event IDs. Dimension values must be all of type dfa:richMediaEventTypeIdAndName.

UserRolesListSortOrder

data UserRolesListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

URLSOAscending
ASCENDING
URLSODescending
DESCENDING

Instances

Enum UserRolesListSortOrder Source # 
Eq UserRolesListSortOrder Source # 
Data UserRolesListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserRolesListSortOrder -> c UserRolesListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserRolesListSortOrder #

toConstr :: UserRolesListSortOrder -> Constr #

dataTypeOf :: UserRolesListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserRolesListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserRolesListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> UserRolesListSortOrder -> UserRolesListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserRolesListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserRolesListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserRolesListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserRolesListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserRolesListSortOrder -> m UserRolesListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRolesListSortOrder -> m UserRolesListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRolesListSortOrder -> m UserRolesListSortOrder #

Ord UserRolesListSortOrder Source # 
Read UserRolesListSortOrder Source # 
Show UserRolesListSortOrder Source # 
Generic UserRolesListSortOrder Source # 
Hashable UserRolesListSortOrder Source # 
ToJSON UserRolesListSortOrder Source # 
FromJSON UserRolesListSortOrder Source # 
FromHttpApiData UserRolesListSortOrder Source # 
ToHttpApiData UserRolesListSortOrder Source # 
type Rep UserRolesListSortOrder Source # 
type Rep UserRolesListSortOrder = D1 (MetaData "UserRolesListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "URLSOAscending" PrefixI False) U1) (C1 (MetaCons "URLSODescending" PrefixI False) U1))

PlacementsListCompatibilities

data PlacementsListCompatibilities Source #

Select only placements that are associated with these compatibilities. DISPLAY and DISPLAY_INTERSTITIAL refer to rendering either on desktop or on mobile devices for regular or interstitial ads respectively. APP and APP_INTERSTITIAL are for rendering in mobile apps. IN_STREAM_VIDEO refers to rendering in in-stream video ads developed with the VAST standard.

Constructors

PLCApp
APP
PLCAppInterstitial
APP_INTERSTITIAL
PLCDisplay
DISPLAY
PLCDisplayInterstitial
DISPLAY_INTERSTITIAL
PLCInStreamVideo
IN_STREAM_VIDEO

Instances

Enum PlacementsListCompatibilities Source # 
Eq PlacementsListCompatibilities Source # 
Data PlacementsListCompatibilities Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementsListCompatibilities -> c PlacementsListCompatibilities #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementsListCompatibilities #

toConstr :: PlacementsListCompatibilities -> Constr #

dataTypeOf :: PlacementsListCompatibilities -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementsListCompatibilities) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementsListCompatibilities) #

gmapT :: (forall b. Data b => b -> b) -> PlacementsListCompatibilities -> PlacementsListCompatibilities #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementsListCompatibilities -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementsListCompatibilities -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementsListCompatibilities -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementsListCompatibilities -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementsListCompatibilities -> m PlacementsListCompatibilities #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementsListCompatibilities -> m PlacementsListCompatibilities #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementsListCompatibilities -> m PlacementsListCompatibilities #

Ord PlacementsListCompatibilities Source # 
Read PlacementsListCompatibilities Source # 
Show PlacementsListCompatibilities Source # 
Generic PlacementsListCompatibilities Source # 
Hashable PlacementsListCompatibilities Source # 
ToJSON PlacementsListCompatibilities Source # 
FromJSON PlacementsListCompatibilities Source # 
FromHttpApiData PlacementsListCompatibilities Source # 
ToHttpApiData PlacementsListCompatibilities Source # 
type Rep PlacementsListCompatibilities Source # 
type Rep PlacementsListCompatibilities = D1 (MetaData "PlacementsListCompatibilities" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "PLCApp" PrefixI False) U1) (C1 (MetaCons "PLCAppInterstitial" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PLCDisplay" PrefixI False) U1) ((:+:) (C1 (MetaCons "PLCDisplayInterstitial" PrefixI False) U1) (C1 (MetaCons "PLCInStreamVideo" PrefixI False) U1))))

TargetableRemarketingListsListResponse

data TargetableRemarketingListsListResponse Source #

Targetable remarketing list response

See: targetableRemarketingListsListResponse smart constructor.

Instances

Eq TargetableRemarketingListsListResponse Source # 
Data TargetableRemarketingListsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TargetableRemarketingListsListResponse -> c TargetableRemarketingListsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TargetableRemarketingListsListResponse #

toConstr :: TargetableRemarketingListsListResponse -> Constr #

dataTypeOf :: TargetableRemarketingListsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TargetableRemarketingListsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TargetableRemarketingListsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> TargetableRemarketingListsListResponse -> TargetableRemarketingListsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TargetableRemarketingListsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TargetableRemarketingListsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> TargetableRemarketingListsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TargetableRemarketingListsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TargetableRemarketingListsListResponse -> m TargetableRemarketingListsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetableRemarketingListsListResponse -> m TargetableRemarketingListsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetableRemarketingListsListResponse -> m TargetableRemarketingListsListResponse #

Show TargetableRemarketingListsListResponse Source # 
Generic TargetableRemarketingListsListResponse Source # 
ToJSON TargetableRemarketingListsListResponse Source # 
FromJSON TargetableRemarketingListsListResponse Source # 
type Rep TargetableRemarketingListsListResponse Source # 
type Rep TargetableRemarketingListsListResponse = D1 (MetaData "TargetableRemarketingListsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "TargetableRemarketingListsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_trllrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_trllrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_trllrTargetableRemarketingLists") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [TargetableRemarketingList]))))))

targetableRemarketingListsListResponse :: TargetableRemarketingListsListResponse Source #

Creates a value of TargetableRemarketingListsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

trllrNextPageToken :: Lens' TargetableRemarketingListsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

trllrKind :: Lens' TargetableRemarketingListsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#targetableRemarketingListsListResponse".

OrderDocumentsListSortField

data OrderDocumentsListSortField Source #

Field by which to sort the list.

Constructors

ODLSFID
ID
ODLSFName
NAME

Instances

Enum OrderDocumentsListSortField Source # 
Eq OrderDocumentsListSortField Source # 
Data OrderDocumentsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderDocumentsListSortField -> c OrderDocumentsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderDocumentsListSortField #

toConstr :: OrderDocumentsListSortField -> Constr #

dataTypeOf :: OrderDocumentsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderDocumentsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderDocumentsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> OrderDocumentsListSortField -> OrderDocumentsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderDocumentsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderDocumentsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderDocumentsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderDocumentsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderDocumentsListSortField -> m OrderDocumentsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderDocumentsListSortField -> m OrderDocumentsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderDocumentsListSortField -> m OrderDocumentsListSortField #

Ord OrderDocumentsListSortField Source # 
Read OrderDocumentsListSortField Source # 
Show OrderDocumentsListSortField Source # 
Generic OrderDocumentsListSortField Source # 
Hashable OrderDocumentsListSortField Source # 
ToJSON OrderDocumentsListSortField Source # 
FromJSON OrderDocumentsListSortField Source # 
FromHttpApiData OrderDocumentsListSortField Source # 
ToHttpApiData OrderDocumentsListSortField Source # 
type Rep OrderDocumentsListSortField Source # 
type Rep OrderDocumentsListSortField = D1 (MetaData "OrderDocumentsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ODLSFID" PrefixI False) U1) (C1 (MetaCons "ODLSFName" PrefixI False) U1))

CreativeCompatibilityItem

data CreativeCompatibilityItem Source #

Constructors

CCIApp
APP
CCIAppInterstitial
APP_INTERSTITIAL
CCIDisplay
DISPLAY
CCIDisplayInterstitial
DISPLAY_INTERSTITIAL
CCIInStreamVideo
IN_STREAM_VIDEO

Instances

Enum CreativeCompatibilityItem Source # 
Eq CreativeCompatibilityItem Source # 
Data CreativeCompatibilityItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeCompatibilityItem -> c CreativeCompatibilityItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeCompatibilityItem #

toConstr :: CreativeCompatibilityItem -> Constr #

dataTypeOf :: CreativeCompatibilityItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeCompatibilityItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeCompatibilityItem) #

gmapT :: (forall b. Data b => b -> b) -> CreativeCompatibilityItem -> CreativeCompatibilityItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeCompatibilityItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeCompatibilityItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeCompatibilityItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeCompatibilityItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeCompatibilityItem -> m CreativeCompatibilityItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeCompatibilityItem -> m CreativeCompatibilityItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeCompatibilityItem -> m CreativeCompatibilityItem #

Ord CreativeCompatibilityItem Source # 
Read CreativeCompatibilityItem Source # 
Show CreativeCompatibilityItem Source # 
Generic CreativeCompatibilityItem Source # 
Hashable CreativeCompatibilityItem Source # 
ToJSON CreativeCompatibilityItem Source # 
FromJSON CreativeCompatibilityItem Source # 
FromHttpApiData CreativeCompatibilityItem Source # 
ToHttpApiData CreativeCompatibilityItem Source # 
type Rep CreativeCompatibilityItem Source # 
type Rep CreativeCompatibilityItem = D1 (MetaData "CreativeCompatibilityItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "CCIApp" PrefixI False) U1) (C1 (MetaCons "CCIAppInterstitial" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CCIDisplay" PrefixI False) U1) ((:+:) (C1 (MetaCons "CCIDisplayInterstitial" PrefixI False) U1) (C1 (MetaCons "CCIInStreamVideo" PrefixI False) U1))))

ChangeLogsListResponse

data ChangeLogsListResponse Source #

Change Log List Response

See: changeLogsListResponse smart constructor.

Instances

Eq ChangeLogsListResponse Source # 
Data ChangeLogsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChangeLogsListResponse -> c ChangeLogsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChangeLogsListResponse #

toConstr :: ChangeLogsListResponse -> Constr #

dataTypeOf :: ChangeLogsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChangeLogsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChangeLogsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> ChangeLogsListResponse -> ChangeLogsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChangeLogsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChangeLogsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChangeLogsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChangeLogsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChangeLogsListResponse -> m ChangeLogsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeLogsListResponse -> m ChangeLogsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeLogsListResponse -> m ChangeLogsListResponse #

Show ChangeLogsListResponse Source # 
Generic ChangeLogsListResponse Source # 
ToJSON ChangeLogsListResponse Source # 
FromJSON ChangeLogsListResponse Source # 
type Rep ChangeLogsListResponse Source # 
type Rep ChangeLogsListResponse = D1 (MetaData "ChangeLogsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ChangeLogsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cllrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cllrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_cllrChangeLogs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ChangeLog]))))))

changeLogsListResponse :: ChangeLogsListResponse Source #

Creates a value of ChangeLogsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cllrNextPageToken :: Lens' ChangeLogsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

cllrKind :: Lens' ChangeLogsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#changeLogsListResponse".

ReportDeliveryEmailOwnerDeliveryType

data ReportDeliveryEmailOwnerDeliveryType Source #

The type of delivery for the owner to receive, if enabled.

Constructors

RDEODTAttachment
ATTACHMENT
RDEODTLink
LINK

Instances

Enum ReportDeliveryEmailOwnerDeliveryType Source # 
Eq ReportDeliveryEmailOwnerDeliveryType Source # 
Data ReportDeliveryEmailOwnerDeliveryType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportDeliveryEmailOwnerDeliveryType -> c ReportDeliveryEmailOwnerDeliveryType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportDeliveryEmailOwnerDeliveryType #

toConstr :: ReportDeliveryEmailOwnerDeliveryType -> Constr #

dataTypeOf :: ReportDeliveryEmailOwnerDeliveryType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportDeliveryEmailOwnerDeliveryType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportDeliveryEmailOwnerDeliveryType) #

gmapT :: (forall b. Data b => b -> b) -> ReportDeliveryEmailOwnerDeliveryType -> ReportDeliveryEmailOwnerDeliveryType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportDeliveryEmailOwnerDeliveryType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportDeliveryEmailOwnerDeliveryType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportDeliveryEmailOwnerDeliveryType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportDeliveryEmailOwnerDeliveryType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportDeliveryEmailOwnerDeliveryType -> m ReportDeliveryEmailOwnerDeliveryType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportDeliveryEmailOwnerDeliveryType -> m ReportDeliveryEmailOwnerDeliveryType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportDeliveryEmailOwnerDeliveryType -> m ReportDeliveryEmailOwnerDeliveryType #

Ord ReportDeliveryEmailOwnerDeliveryType Source # 
Read ReportDeliveryEmailOwnerDeliveryType Source # 
Show ReportDeliveryEmailOwnerDeliveryType Source # 
Generic ReportDeliveryEmailOwnerDeliveryType Source # 
Hashable ReportDeliveryEmailOwnerDeliveryType Source # 
ToJSON ReportDeliveryEmailOwnerDeliveryType Source # 
FromJSON ReportDeliveryEmailOwnerDeliveryType Source # 
FromHttpApiData ReportDeliveryEmailOwnerDeliveryType Source # 
ToHttpApiData ReportDeliveryEmailOwnerDeliveryType Source # 
type Rep ReportDeliveryEmailOwnerDeliveryType Source # 
type Rep ReportDeliveryEmailOwnerDeliveryType = D1 (MetaData "ReportDeliveryEmailOwnerDeliveryType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "RDEODTAttachment" PrefixI False) U1) (C1 (MetaCons "RDEODTLink" PrefixI False) U1))

SiteContactContactType

data SiteContactContactType Source #

Site contact type.

Constructors

SalesPerson
SALES_PERSON
Trafficker
TRAFFICKER

Instances

Enum SiteContactContactType Source # 
Eq SiteContactContactType Source # 
Data SiteContactContactType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SiteContactContactType -> c SiteContactContactType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SiteContactContactType #

toConstr :: SiteContactContactType -> Constr #

dataTypeOf :: SiteContactContactType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SiteContactContactType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SiteContactContactType) #

gmapT :: (forall b. Data b => b -> b) -> SiteContactContactType -> SiteContactContactType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SiteContactContactType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SiteContactContactType -> r #

gmapQ :: (forall d. Data d => d -> u) -> SiteContactContactType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SiteContactContactType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SiteContactContactType -> m SiteContactContactType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SiteContactContactType -> m SiteContactContactType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SiteContactContactType -> m SiteContactContactType #

Ord SiteContactContactType Source # 
Read SiteContactContactType Source # 
Show SiteContactContactType Source # 
Generic SiteContactContactType Source # 
Hashable SiteContactContactType Source # 
ToJSON SiteContactContactType Source # 
FromJSON SiteContactContactType Source # 
FromHttpApiData SiteContactContactType Source # 
ToHttpApiData SiteContactContactType Source # 
type Rep SiteContactContactType Source # 
type Rep SiteContactContactType = D1 (MetaData "SiteContactContactType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "SalesPerson" PrefixI False) U1) (C1 (MetaCons "Trafficker" PrefixI False) U1))

AccountUserProFile

data AccountUserProFile Source #

AccountUserProfiles contains properties of a DCM user profile. This resource is specifically for managing user profiles, whereas UserProfiles is for accessing the API.

See: accountUserProFile smart constructor.

Instances

Eq AccountUserProFile Source # 
Data AccountUserProFile Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountUserProFile -> c AccountUserProFile #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountUserProFile #

toConstr :: AccountUserProFile -> Constr #

dataTypeOf :: AccountUserProFile -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountUserProFile) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountUserProFile) #

gmapT :: (forall b. Data b => b -> b) -> AccountUserProFile -> AccountUserProFile #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountUserProFile -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountUserProFile -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountUserProFile -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountUserProFile -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountUserProFile -> m AccountUserProFile #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountUserProFile -> m AccountUserProFile #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountUserProFile -> m AccountUserProFile #

Show AccountUserProFile Source # 
Generic AccountUserProFile Source # 
ToJSON AccountUserProFile Source # 
FromJSON AccountUserProFile Source # 
type Rep AccountUserProFile Source # 
type Rep AccountUserProFile = D1 (MetaData "AccountUserProFile" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AccountUserProFile'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aupfEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aupfUserRoleFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectFilter)))) ((:*:) (S1 (MetaSel (Just Symbol "_aupfAdvertiserFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectFilter))) (S1 (MetaSel (Just Symbol "_aupfUserRoleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aupfKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_aupfLocale") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_aupfSiteFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectFilter))) (S1 (MetaSel (Just Symbol "_aupfTraffickerType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AccountUserProFileTraffickerType)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aupfActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_aupfAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_aupfName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aupfId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aupfUserAccessType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AccountUserProFileUserAccessType))) (S1 (MetaSel (Just Symbol "_aupfComments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_aupfSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_aupfCampaignFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ObjectFilter))))))))

aupfEmail :: Lens' AccountUserProFile (Maybe Text) Source #

Email of the user profile. The email addresss must be linked to a Google Account. This field is required on insertion and is read-only after insertion.

aupfUserRoleFilter :: Lens' AccountUserProFile (Maybe ObjectFilter) Source #

Filter that describes which user roles are visible to the user profile.

aupfAdvertiserFilter :: Lens' AccountUserProFile (Maybe ObjectFilter) Source #

Filter that describes which advertisers are visible to the user profile.

aupfUserRoleId :: Lens' AccountUserProFile (Maybe Int64) Source #

User role ID of the user profile. This is a required field.

aupfKind :: Lens' AccountUserProFile Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#accountUserProfile".

aupfLocale :: Lens' AccountUserProFile (Maybe Text) Source #

Locale of the user profile. This is a required field. Acceptable values are: - "cs" (Czech) - "de" (German) - "en" (English) - "en-GB" (English United Kingdom) - "es" (Spanish) - "fr" (French) - "it" (Italian) - "ja" (Japanese) - "ko" (Korean) - "pl" (Polish) - "pt-BR" (Portuguese Brazil) - "ru" (Russian) - "sv" (Swedish) - "tr" (Turkish) - "zh-CN" (Chinese Simplified) - "zh-TW" (Chinese Traditional)

aupfSiteFilter :: Lens' AccountUserProFile (Maybe ObjectFilter) Source #

Filter that describes which sites are visible to the user profile.

aupfActive :: Lens' AccountUserProFile (Maybe Bool) Source #

Whether this user profile is active. This defaults to false, and must be set true on insert for the user profile to be usable.

aupfAccountId :: Lens' AccountUserProFile (Maybe Int64) Source #

Account ID of the user profile. This is a read-only field that can be left blank.

aupfName :: Lens' AccountUserProFile (Maybe Text) Source #

Name of the user profile. This is a required field. Must be less than 64 characters long, must be globally unique, and cannot contain whitespace or any of the following characters: "&;"#%,".

aupfId :: Lens' AccountUserProFile (Maybe Int64) Source #

ID of the user profile. This is a read-only, auto-generated field.

aupfUserAccessType :: Lens' AccountUserProFile (Maybe AccountUserProFileUserAccessType) Source #

User type of the user profile. This is a read-only field that can be left blank.

aupfComments :: Lens' AccountUserProFile (Maybe Text) Source #

Comments for this user profile.

aupfSubAccountId :: Lens' AccountUserProFile (Maybe Int64) Source #

Subaccount ID of the user profile. This is a read-only field that can be left blank.

aupfCampaignFilter :: Lens' AccountUserProFile (Maybe ObjectFilter) Source #

Filter that describes which campaigns are visible to the user profile.

ReportsListSortOrder

data ReportsListSortOrder Source #

Order of sorted results, default is 'DESCENDING'.

Constructors

RLSOAscending

ASCENDING Ascending order.

RLSODescending

DESCENDING Descending order.

Instances

Enum ReportsListSortOrder Source # 
Eq ReportsListSortOrder Source # 
Data ReportsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportsListSortOrder -> c ReportsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportsListSortOrder #

toConstr :: ReportsListSortOrder -> Constr #

dataTypeOf :: ReportsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> ReportsListSortOrder -> ReportsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportsListSortOrder -> m ReportsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportsListSortOrder -> m ReportsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportsListSortOrder -> m ReportsListSortOrder #

Ord ReportsListSortOrder Source # 
Read ReportsListSortOrder Source # 
Show ReportsListSortOrder Source # 
Generic ReportsListSortOrder Source # 
Hashable ReportsListSortOrder Source # 
ToJSON ReportsListSortOrder Source # 
FromJSON ReportsListSortOrder Source # 
FromHttpApiData ReportsListSortOrder Source # 
ToHttpApiData ReportsListSortOrder Source # 
type Rep ReportsListSortOrder Source # 
type Rep ReportsListSortOrder = D1 (MetaData "ReportsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "RLSOAscending" PrefixI False) U1) (C1 (MetaCons "RLSODescending" PrefixI False) U1))

DimensionValue

data DimensionValue Source #

Represents a DimensionValue resource.

See: dimensionValue smart constructor.

Instances

Eq DimensionValue Source # 
Data DimensionValue Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DimensionValue -> c DimensionValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DimensionValue #

toConstr :: DimensionValue -> Constr #

dataTypeOf :: DimensionValue -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DimensionValue) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DimensionValue) #

gmapT :: (forall b. Data b => b -> b) -> DimensionValue -> DimensionValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DimensionValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DimensionValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> DimensionValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DimensionValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DimensionValue -> m DimensionValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionValue -> m DimensionValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionValue -> m DimensionValue #

Show DimensionValue Source # 
Generic DimensionValue Source # 

Associated Types

type Rep DimensionValue :: * -> * #

ToJSON DimensionValue Source # 
FromJSON DimensionValue Source # 
type Rep DimensionValue Source # 

dimensionValue :: DimensionValue Source #

Creates a value of DimensionValue with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dvEtag :: Lens' DimensionValue (Maybe Text) Source #

The eTag of this response for caching purposes.

dvKind :: Lens' DimensionValue Text Source #

The kind of resource this is, in this case dfareporting#dimensionValue.

dvValue :: Lens' DimensionValue (Maybe Text) Source #

The value of the dimension.

dvMatchType :: Lens' DimensionValue (Maybe DimensionValueMatchType) Source #

Determines how the 'value' field is matched when filtering. If not specified, defaults to EXACT. If set to WILDCARD_EXPRESSION, '*' is allowed as a placeholder for variable length character sequences, and it can be escaped with a backslash. Note, only paid search dimensions ('dfa:paidSearch*') allow a matchType other than EXACT.

dvDimensionName :: Lens' DimensionValue (Maybe Text) Source #

The name of the dimension.

dvId :: Lens' DimensionValue (Maybe Text) Source #

The ID associated with the value if available.

TargetableRemarketingListsListSortField

data TargetableRemarketingListsListSortField Source #

Field by which to sort the list.

Constructors

TRLLSFID
ID
TRLLSFName
NAME

Instances

Enum TargetableRemarketingListsListSortField Source # 
Eq TargetableRemarketingListsListSortField Source # 
Data TargetableRemarketingListsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TargetableRemarketingListsListSortField -> c TargetableRemarketingListsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TargetableRemarketingListsListSortField #

toConstr :: TargetableRemarketingListsListSortField -> Constr #

dataTypeOf :: TargetableRemarketingListsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TargetableRemarketingListsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TargetableRemarketingListsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> TargetableRemarketingListsListSortField -> TargetableRemarketingListsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TargetableRemarketingListsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TargetableRemarketingListsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> TargetableRemarketingListsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TargetableRemarketingListsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TargetableRemarketingListsListSortField -> m TargetableRemarketingListsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetableRemarketingListsListSortField -> m TargetableRemarketingListsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetableRemarketingListsListSortField -> m TargetableRemarketingListsListSortField #

Ord TargetableRemarketingListsListSortField Source # 
Read TargetableRemarketingListsListSortField Source # 
Show TargetableRemarketingListsListSortField Source # 
Generic TargetableRemarketingListsListSortField Source # 
Hashable TargetableRemarketingListsListSortField Source # 
ToJSON TargetableRemarketingListsListSortField Source # 
FromJSON TargetableRemarketingListsListSortField Source # 
FromHttpApiData TargetableRemarketingListsListSortField Source # 
ToHttpApiData TargetableRemarketingListsListSortField Source # 
type Rep TargetableRemarketingListsListSortField Source # 
type Rep TargetableRemarketingListsListSortField = D1 (MetaData "TargetableRemarketingListsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "TRLLSFID" PrefixI False) U1) (C1 (MetaCons "TRLLSFName" PrefixI False) U1))

CampaignsListSortOrder

data CampaignsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

CLSOAscending
ASCENDING
CLSODescending
DESCENDING

Instances

Enum CampaignsListSortOrder Source # 
Eq CampaignsListSortOrder Source # 
Data CampaignsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CampaignsListSortOrder -> c CampaignsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CampaignsListSortOrder #

toConstr :: CampaignsListSortOrder -> Constr #

dataTypeOf :: CampaignsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CampaignsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CampaignsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> CampaignsListSortOrder -> CampaignsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CampaignsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CampaignsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> CampaignsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CampaignsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CampaignsListSortOrder -> m CampaignsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignsListSortOrder -> m CampaignsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignsListSortOrder -> m CampaignsListSortOrder #

Ord CampaignsListSortOrder Source # 
Read CampaignsListSortOrder Source # 
Show CampaignsListSortOrder Source # 
Generic CampaignsListSortOrder Source # 
Hashable CampaignsListSortOrder Source # 
ToJSON CampaignsListSortOrder Source # 
FromJSON CampaignsListSortOrder Source # 
FromHttpApiData CampaignsListSortOrder Source # 
ToHttpApiData CampaignsListSortOrder Source # 
type Rep CampaignsListSortOrder Source # 
type Rep CampaignsListSortOrder = D1 (MetaData "CampaignsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CLSOAscending" PrefixI False) U1) (C1 (MetaCons "CLSODescending" PrefixI False) U1))

Activities

data Activities Source #

Represents an activity group.

See: activities smart constructor.

Instances

Eq Activities Source # 
Data Activities Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Activities -> c Activities #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Activities #

toConstr :: Activities -> Constr #

dataTypeOf :: Activities -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Activities) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Activities) #

gmapT :: (forall b. Data b => b -> b) -> Activities -> Activities #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Activities -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Activities -> r #

gmapQ :: (forall d. Data d => d -> u) -> Activities -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Activities -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Activities -> m Activities #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Activities -> m Activities #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Activities -> m Activities #

Show Activities Source # 
Generic Activities Source # 

Associated Types

type Rep Activities :: * -> * #

ToJSON Activities Source # 
FromJSON Activities Source # 
type Rep Activities Source # 
type Rep Activities = D1 (MetaData "Activities" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Activities'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_actKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_actMetricNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_actFilters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DimensionValue]))))))

activities :: Activities Source #

Creates a value of Activities with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

actKind :: Lens' Activities Text Source #

The kind of resource this is, in this case dfareporting#activities.

actMetricNames :: Lens' Activities [Text] Source #

List of names of floodlight activity metrics.

actFilters :: Lens' Activities [DimensionValue] Source #

List of activity filters. The dimension values need to be all either of type "dfa:activity" or "dfa:activityGroup".

FloodlightActivityGroupsListType

data FloodlightActivityGroupsListType Source #

Select only floodlight activity groups with the specified floodlight activity group type.

Constructors

Counter
COUNTER
Sale
SALE

Instances

Enum FloodlightActivityGroupsListType Source # 
Eq FloodlightActivityGroupsListType Source # 
Data FloodlightActivityGroupsListType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivityGroupsListType -> c FloodlightActivityGroupsListType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivityGroupsListType #

toConstr :: FloodlightActivityGroupsListType -> Constr #

dataTypeOf :: FloodlightActivityGroupsListType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivityGroupsListType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivityGroupsListType) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivityGroupsListType -> FloodlightActivityGroupsListType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityGroupsListType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityGroupsListType -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivityGroupsListType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivityGroupsListType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupsListType -> m FloodlightActivityGroupsListType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupsListType -> m FloodlightActivityGroupsListType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupsListType -> m FloodlightActivityGroupsListType #

Ord FloodlightActivityGroupsListType Source # 
Read FloodlightActivityGroupsListType Source # 
Show FloodlightActivityGroupsListType Source # 
Generic FloodlightActivityGroupsListType Source # 
Hashable FloodlightActivityGroupsListType Source # 
ToJSON FloodlightActivityGroupsListType Source # 
FromJSON FloodlightActivityGroupsListType Source # 
FromHttpApiData FloodlightActivityGroupsListType Source # 
ToHttpApiData FloodlightActivityGroupsListType Source # 
type Rep FloodlightActivityGroupsListType Source # 
type Rep FloodlightActivityGroupsListType = D1 (MetaData "FloodlightActivityGroupsListType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Counter" PrefixI False) U1) (C1 (MetaCons "Sale" PrefixI False) U1))

FloodlightConfigurationFirstDayOfWeek

data FloodlightConfigurationFirstDayOfWeek Source #

Day that will be counted as the first day of the week in reports. This is a required field.

Constructors

Monday
MONDAY
Sunday
SUNDAY

Instances

Enum FloodlightConfigurationFirstDayOfWeek Source # 
Eq FloodlightConfigurationFirstDayOfWeek Source # 
Data FloodlightConfigurationFirstDayOfWeek Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightConfigurationFirstDayOfWeek -> c FloodlightConfigurationFirstDayOfWeek #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightConfigurationFirstDayOfWeek #

toConstr :: FloodlightConfigurationFirstDayOfWeek -> Constr #

dataTypeOf :: FloodlightConfigurationFirstDayOfWeek -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightConfigurationFirstDayOfWeek) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightConfigurationFirstDayOfWeek) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightConfigurationFirstDayOfWeek -> FloodlightConfigurationFirstDayOfWeek #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightConfigurationFirstDayOfWeek -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightConfigurationFirstDayOfWeek -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightConfigurationFirstDayOfWeek -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightConfigurationFirstDayOfWeek -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightConfigurationFirstDayOfWeek -> m FloodlightConfigurationFirstDayOfWeek #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightConfigurationFirstDayOfWeek -> m FloodlightConfigurationFirstDayOfWeek #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightConfigurationFirstDayOfWeek -> m FloodlightConfigurationFirstDayOfWeek #

Ord FloodlightConfigurationFirstDayOfWeek Source # 
Read FloodlightConfigurationFirstDayOfWeek Source # 
Show FloodlightConfigurationFirstDayOfWeek Source # 
Generic FloodlightConfigurationFirstDayOfWeek Source # 
Hashable FloodlightConfigurationFirstDayOfWeek Source # 
ToJSON FloodlightConfigurationFirstDayOfWeek Source # 
FromJSON FloodlightConfigurationFirstDayOfWeek Source # 
FromHttpApiData FloodlightConfigurationFirstDayOfWeek Source # 
ToHttpApiData FloodlightConfigurationFirstDayOfWeek Source # 
type Rep FloodlightConfigurationFirstDayOfWeek Source # 
type Rep FloodlightConfigurationFirstDayOfWeek = D1 (MetaData "FloodlightConfigurationFirstDayOfWeek" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Monday" PrefixI False) U1) (C1 (MetaCons "Sunday" PrefixI False) U1))

UserRolePermissionGroupsListResponse

data UserRolePermissionGroupsListResponse Source #

User Role Permission Group List Response

See: userRolePermissionGroupsListResponse smart constructor.

Instances

Eq UserRolePermissionGroupsListResponse Source # 
Data UserRolePermissionGroupsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserRolePermissionGroupsListResponse -> c UserRolePermissionGroupsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserRolePermissionGroupsListResponse #

toConstr :: UserRolePermissionGroupsListResponse -> Constr #

dataTypeOf :: UserRolePermissionGroupsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserRolePermissionGroupsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserRolePermissionGroupsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> UserRolePermissionGroupsListResponse -> UserRolePermissionGroupsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserRolePermissionGroupsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserRolePermissionGroupsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserRolePermissionGroupsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserRolePermissionGroupsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserRolePermissionGroupsListResponse -> m UserRolePermissionGroupsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRolePermissionGroupsListResponse -> m UserRolePermissionGroupsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRolePermissionGroupsListResponse -> m UserRolePermissionGroupsListResponse #

Show UserRolePermissionGroupsListResponse Source # 
Generic UserRolePermissionGroupsListResponse Source # 
ToJSON UserRolePermissionGroupsListResponse Source # 
FromJSON UserRolePermissionGroupsListResponse Source # 
type Rep UserRolePermissionGroupsListResponse Source # 
type Rep UserRolePermissionGroupsListResponse = D1 (MetaData "UserRolePermissionGroupsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "UserRolePermissionGroupsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_urpglrUserRolePermissionGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UserRolePermissionGroup]))) (S1 (MetaSel (Just Symbol "_urpglrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

userRolePermissionGroupsListResponse :: UserRolePermissionGroupsListResponse Source #

Creates a value of UserRolePermissionGroupsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

urpglrKind :: Lens' UserRolePermissionGroupsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#userRolePermissionGroupsListResponse".

PlacementTag

data PlacementTag Source #

Placement Tag

See: placementTag smart constructor.

Instances

Eq PlacementTag Source # 
Data PlacementTag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementTag -> c PlacementTag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementTag #

toConstr :: PlacementTag -> Constr #

dataTypeOf :: PlacementTag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementTag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementTag) #

gmapT :: (forall b. Data b => b -> b) -> PlacementTag -> PlacementTag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementTag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementTag -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementTag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementTag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementTag -> m PlacementTag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementTag -> m PlacementTag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementTag -> m PlacementTag #

Show PlacementTag Source # 
Generic PlacementTag Source # 

Associated Types

type Rep PlacementTag :: * -> * #

ToJSON PlacementTag Source # 
FromJSON PlacementTag Source # 
type Rep PlacementTag Source # 
type Rep PlacementTag = D1 (MetaData "PlacementTag" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PlacementTag'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ptPlacementId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_ptTagDatas") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [TagData])))))

placementTag :: PlacementTag Source #

Creates a value of PlacementTag with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ptTagDatas :: Lens' PlacementTag [TagData] Source #

Tags generated for this placement.

DeliverySchedulePriority

data DeliverySchedulePriority Source #

Serving priority of an ad, with respect to other ads. The lower the priority number, the greater the priority with which it is served.

Constructors

AdPriority01
AD_PRIORITY_01
AdPriority02
AD_PRIORITY_02
AdPriority03
AD_PRIORITY_03
AdPriority04
AD_PRIORITY_04
AdPriority05
AD_PRIORITY_05
AdPriority06
AD_PRIORITY_06
AdPriority07
AD_PRIORITY_07
AdPriority08
AD_PRIORITY_08
AdPriority09
AD_PRIORITY_09
AdPriority10
AD_PRIORITY_10
AdPriority11
AD_PRIORITY_11
AdPriority12
AD_PRIORITY_12
AdPriority13
AD_PRIORITY_13
AdPriority14
AD_PRIORITY_14
AdPriority15
AD_PRIORITY_15
AdPriority16
AD_PRIORITY_16

Instances

Enum DeliverySchedulePriority Source # 
Eq DeliverySchedulePriority Source # 
Data DeliverySchedulePriority Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeliverySchedulePriority -> c DeliverySchedulePriority #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeliverySchedulePriority #

toConstr :: DeliverySchedulePriority -> Constr #

dataTypeOf :: DeliverySchedulePriority -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeliverySchedulePriority) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeliverySchedulePriority) #

gmapT :: (forall b. Data b => b -> b) -> DeliverySchedulePriority -> DeliverySchedulePriority #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeliverySchedulePriority -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeliverySchedulePriority -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeliverySchedulePriority -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeliverySchedulePriority -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeliverySchedulePriority -> m DeliverySchedulePriority #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeliverySchedulePriority -> m DeliverySchedulePriority #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeliverySchedulePriority -> m DeliverySchedulePriority #

Ord DeliverySchedulePriority Source # 
Read DeliverySchedulePriority Source # 
Show DeliverySchedulePriority Source # 
Generic DeliverySchedulePriority Source # 
Hashable DeliverySchedulePriority Source # 
ToJSON DeliverySchedulePriority Source # 
FromJSON DeliverySchedulePriority Source # 
FromHttpApiData DeliverySchedulePriority Source # 
ToHttpApiData DeliverySchedulePriority Source # 
type Rep DeliverySchedulePriority Source # 
type Rep DeliverySchedulePriority = D1 (MetaData "DeliverySchedulePriority" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "AdPriority01" PrefixI False) U1) (C1 (MetaCons "AdPriority02" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AdPriority03" PrefixI False) U1) (C1 (MetaCons "AdPriority04" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "AdPriority05" PrefixI False) U1) (C1 (MetaCons "AdPriority06" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AdPriority07" PrefixI False) U1) (C1 (MetaCons "AdPriority08" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "AdPriority09" PrefixI False) U1) (C1 (MetaCons "AdPriority10" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AdPriority11" PrefixI False) U1) (C1 (MetaCons "AdPriority12" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "AdPriority13" PrefixI False) U1) (C1 (MetaCons "AdPriority14" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AdPriority15" PrefixI False) U1) (C1 (MetaCons "AdPriority16" PrefixI False) U1)))))

FloodlightActivitiesListFloodlightActivityGroupType

data FloodlightActivitiesListFloodlightActivityGroupType Source #

Select only floodlight activities with the specified floodlight activity group type.

Constructors

FALFAGTCounter
COUNTER
FALFAGTSale
SALE

Instances

Enum FloodlightActivitiesListFloodlightActivityGroupType Source # 
Eq FloodlightActivitiesListFloodlightActivityGroupType Source # 
Data FloodlightActivitiesListFloodlightActivityGroupType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivitiesListFloodlightActivityGroupType -> c FloodlightActivitiesListFloodlightActivityGroupType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivitiesListFloodlightActivityGroupType #

toConstr :: FloodlightActivitiesListFloodlightActivityGroupType -> Constr #

dataTypeOf :: FloodlightActivitiesListFloodlightActivityGroupType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivitiesListFloodlightActivityGroupType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivitiesListFloodlightActivityGroupType) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivitiesListFloodlightActivityGroupType -> FloodlightActivitiesListFloodlightActivityGroupType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivitiesListFloodlightActivityGroupType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivitiesListFloodlightActivityGroupType -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivitiesListFloodlightActivityGroupType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivitiesListFloodlightActivityGroupType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivitiesListFloodlightActivityGroupType -> m FloodlightActivitiesListFloodlightActivityGroupType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivitiesListFloodlightActivityGroupType -> m FloodlightActivitiesListFloodlightActivityGroupType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivitiesListFloodlightActivityGroupType -> m FloodlightActivitiesListFloodlightActivityGroupType #

Ord FloodlightActivitiesListFloodlightActivityGroupType Source # 
Read FloodlightActivitiesListFloodlightActivityGroupType Source # 
Show FloodlightActivitiesListFloodlightActivityGroupType Source # 
Generic FloodlightActivitiesListFloodlightActivityGroupType Source # 
Hashable FloodlightActivitiesListFloodlightActivityGroupType Source # 
ToJSON FloodlightActivitiesListFloodlightActivityGroupType Source # 
FromJSON FloodlightActivitiesListFloodlightActivityGroupType Source # 
FromHttpApiData FloodlightActivitiesListFloodlightActivityGroupType Source # 
ToHttpApiData FloodlightActivitiesListFloodlightActivityGroupType Source # 
type Rep FloodlightActivitiesListFloodlightActivityGroupType Source # 
type Rep FloodlightActivitiesListFloodlightActivityGroupType = D1 (MetaData "FloodlightActivitiesListFloodlightActivityGroupType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "FALFAGTCounter" PrefixI False) U1) (C1 (MetaCons "FALFAGTSale" PrefixI False) U1))

RemarketingListsListResponse

data RemarketingListsListResponse Source #

Remarketing list response

See: remarketingListsListResponse smart constructor.

Instances

Eq RemarketingListsListResponse Source # 
Data RemarketingListsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RemarketingListsListResponse -> c RemarketingListsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RemarketingListsListResponse #

toConstr :: RemarketingListsListResponse -> Constr #

dataTypeOf :: RemarketingListsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RemarketingListsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RemarketingListsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> RemarketingListsListResponse -> RemarketingListsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RemarketingListsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RemarketingListsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> RemarketingListsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RemarketingListsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RemarketingListsListResponse -> m RemarketingListsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RemarketingListsListResponse -> m RemarketingListsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RemarketingListsListResponse -> m RemarketingListsListResponse #

Show RemarketingListsListResponse Source # 
Generic RemarketingListsListResponse Source # 
ToJSON RemarketingListsListResponse Source # 
FromJSON RemarketingListsListResponse Source # 
type Rep RemarketingListsListResponse Source # 
type Rep RemarketingListsListResponse = D1 (MetaData "RemarketingListsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "RemarketingListsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rllrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rllrRemarketingLists") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RemarketingList]))) (S1 (MetaSel (Just Symbol "_rllrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

remarketingListsListResponse :: RemarketingListsListResponse Source #

Creates a value of RemarketingListsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rllrNextPageToken :: Lens' RemarketingListsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

rllrKind :: Lens' RemarketingListsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#remarketingListsListResponse".

DynamicTargetingKey

data DynamicTargetingKey Source #

Contains properties of a dynamic targeting key. Dynamic targeting keys are unique, user-friendly labels, created at the advertiser level in DCM, that can be assigned to ads, creatives, and placements and used for targeting with DoubleClick Studio dynamic creatives. Use these labels instead of numeric DCM IDs (such as placement IDs) to save time and avoid errors in your dynamic feeds.

See: dynamicTargetingKey smart constructor.

Instances

Eq DynamicTargetingKey Source # 
Data DynamicTargetingKey Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DynamicTargetingKey -> c DynamicTargetingKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DynamicTargetingKey #

toConstr :: DynamicTargetingKey -> Constr #

dataTypeOf :: DynamicTargetingKey -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DynamicTargetingKey) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DynamicTargetingKey) #

gmapT :: (forall b. Data b => b -> b) -> DynamicTargetingKey -> DynamicTargetingKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DynamicTargetingKey -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DynamicTargetingKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> DynamicTargetingKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DynamicTargetingKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DynamicTargetingKey -> m DynamicTargetingKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DynamicTargetingKey -> m DynamicTargetingKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DynamicTargetingKey -> m DynamicTargetingKey #

Show DynamicTargetingKey Source # 
Generic DynamicTargetingKey Source # 
ToJSON DynamicTargetingKey Source # 
FromJSON DynamicTargetingKey Source # 
type Rep DynamicTargetingKey Source # 
type Rep DynamicTargetingKey = D1 (MetaData "DynamicTargetingKey" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DynamicTargetingKey'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dtkObjectType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DynamicTargetingKeyObjectType))) (S1 (MetaSel (Just Symbol "_dtkKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_dtkObjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_dtkName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

dynamicTargetingKey :: DynamicTargetingKey Source #

Creates a value of DynamicTargetingKey with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dtkObjectType :: Lens' DynamicTargetingKey (Maybe DynamicTargetingKeyObjectType) Source #

Type of the object of this dynamic targeting key. This is a required field.

dtkKind :: Lens' DynamicTargetingKey Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#dynamicTargetingKey".

dtkObjectId :: Lens' DynamicTargetingKey (Maybe Int64) Source #

ID of the object of this dynamic targeting key. This is a required field.

dtkName :: Lens' DynamicTargetingKey (Maybe Text) Source #

Name of this dynamic targeting key. This is a required field. Must be less than 256 characters long and cannot contain commas. All characters are converted to lowercase.

Creative

data Creative Source #

Contains properties of a Creative.

See: creative smart constructor.

Instances

Eq Creative Source # 
Data Creative Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Creative -> c Creative #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Creative #

toConstr :: Creative -> Constr #

dataTypeOf :: Creative -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Creative) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Creative) #

gmapT :: (forall b. Data b => b -> b) -> Creative -> Creative #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Creative -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Creative -> r #

gmapQ :: (forall d. Data d => d -> u) -> Creative -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Creative -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Creative -> m Creative #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Creative -> m Creative #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Creative -> m Creative #

Show Creative Source # 
Generic Creative Source # 

Associated Types

type Rep Creative :: * -> * #

Methods

from :: Creative -> Rep Creative x #

to :: Rep Creative x -> Creative #

ToJSON Creative Source # 
FromJSON Creative Source # 
type Rep Creative Source # 
type Rep Creative = D1 (MetaData "Creative" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Creative'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creConvertFlashToHTML5") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_creBackupImageTargetWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TargetWindow))) (S1 (MetaSel (Just Symbol "_creRenderingIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creCustomKeyValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_creVideoDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))) ((:*:) (S1 (MetaSel (Just Symbol "_creRenderingId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_creThirdPartyBackupImageImpressionsURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creFsCommand") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FsCommand))) ((:*:) (S1 (MetaSel (Just Symbol "_creAllowScriptAccess") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_creHTMLCodeLocked") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creRequiredFlashPluginVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_creAuthoringTool") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAuthoringTool)))) ((:*:) (S1 (MetaSel (Just Symbol "_creSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Size))) (S1 (MetaSel (Just Symbol "_creThirdPartyURLs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ThirdPartyTrackingURL]))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creCounterCustomEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeCustomEvent]))) ((:*:) (S1 (MetaSel (Just Symbol "_creKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_creSSLOverride") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creHTMLCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_creAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_creRequiredFlashVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_creBackgRoundColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creAdTagKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_creSkippable") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_creSSLCompliant") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_creIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creBackupImageReportingLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_creCommercialId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_creActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_creExitCustomEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeCustomEvent])))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_creBackupImageClickThroughURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_creName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creOverrideCss") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_creVideoDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_creClickTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ClickTag]))) (S1 (MetaSel (Just Symbol "_creAdParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_creLatestTraffickedCreativeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_creThirdPartyRichMediaImpressionsURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creLastModifiedInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo))) (S1 (MetaSel (Just Symbol "_creId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_creAuthoringSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAuthoringSource))) (S1 (MetaSel (Just Symbol "_creStudioAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creCreativeAssets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeAsset]))) ((:*:) (S1 (MetaSel (Just Symbol "_creSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_creType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeType))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creTimerCustomEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeCustomEvent]))) (S1 (MetaSel (Just Symbol "_creStudioCreativeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_creCompatibility") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeCompatibilityItem]))) (S1 (MetaSel (Just Symbol "_creBackupImageFeatures") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeBackupImageFeaturesItem])))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creArtworkType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeArtworkType))) (S1 (MetaSel (Just Symbol "_creArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_creCompanionCreatives") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64]))) (S1 (MetaSel (Just Symbol "_creTotalFileSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_creStudioTraffickedCreativeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_creRedirectURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_creAutoAdvanceImages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_creCreativeFieldAssignments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeFieldAssignment]))))))))))

creConvertFlashToHTML5 :: Lens' Creative (Maybe Bool) Source #

Whether Flash assets associated with the creative need to be automatically converted to HTML5. This flag is enabled by default and users can choose to disable it if they don't want the system to generate and use HTML5 asset for this creative. Applicable to the following creative type: FLASH_INPAGE. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE.

creBackupImageTargetWindow :: Lens' Creative (Maybe TargetWindow) Source #

Target window for backup image. Applicable to the following creative types: FLASH_INPAGE and HTML5_BANNER. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE.

creRenderingIdDimensionValue :: Lens' Creative (Maybe DimensionValue) Source #

Dimension value for the rendering ID of this creative. This is a read-only field. Applicable to all creative types.

creCustomKeyValues :: Lens' Creative [Text] Source #

Custom key-values for a Rich Media creative. Key-values let you customize the creative settings of a Rich Media ad running on your site without having to contact the advertiser. You can use key-values to dynamically change the look or functionality of a creative. Applicable to the following creative types: all RICH_MEDIA, and all VPAID.

creVideoDuration :: Lens' Creative (Maybe Double) Source #

Creative video duration in seconds. This is a read-only field. Applicable to the following creative types: INSTREAM_VIDEO, all RICH_MEDIA, and all VPAID.

creRenderingId :: Lens' Creative (Maybe Int64) Source #

ID of current rendering version. This is a read-only field. Applicable to all creative types.

creThirdPartyBackupImageImpressionsURL :: Lens' Creative (Maybe Text) Source #

Third-party URL used to record backup image impressions. Applicable to the following creative types: all RICH_MEDIA.

creFsCommand :: Lens' Creative (Maybe FsCommand) Source #

OpenWindow FSCommand of this creative. This lets the SWF file communicate with either Flash Player or the program hosting Flash Player, such as a web browser. This is only triggered if allowScriptAccess field is true. Applicable to the following creative types: FLASH_INPAGE.

creAllowScriptAccess :: Lens' Creative (Maybe Bool) Source #

Whether script access is allowed for this creative. This is a read-only and deprecated field which will automatically be set to true on update. Applicable to the following creative types: FLASH_INPAGE.

creHTMLCodeLocked :: Lens' Creative (Maybe Bool) Source #

Whether HTML code is DCM-generated or manually entered. Set to true to ignore changes to htmlCode. Applicable to the following creative types: FLASH_INPAGE and HTML5_BANNER.

creRequiredFlashPluginVersion :: Lens' Creative (Maybe Text) Source #

The minimum required Flash plugin version for this creative. For example, 11.2.202.235. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA, and all VPAID.

creAuthoringTool :: Lens' Creative (Maybe CreativeAuthoringTool) Source #

Authoring tool for HTML5 banner creatives. This is a read-only field. Applicable to the following creative types: HTML5_BANNER.

creSize :: Lens' Creative (Maybe Size) Source #

Size associated with this creative. When inserting or updating a creative either the size ID field or size width and height fields can be used. This is a required field when applicable; however for IMAGE, FLASH_INPAGE creatives, and for DISPLAY creatives with a primary asset of type HTML_IMAGE, if left blank, this field will be automatically set using the actual size of the associated image assets. Applicable to the following creative types: DISPLAY, DISPLAY_IMAGE_GALLERY, FLASH_INPAGE, HTML5_BANNER, IMAGE, and all RICH_MEDIA.

creThirdPartyURLs :: Lens' Creative [ThirdPartyTrackingURL] Source #

Third-party URLs for tracking in-stream video creative events. Applicable to the following creative types: all INSTREAM_VIDEO and all VPAID.

creCounterCustomEvents :: Lens' Creative [CreativeCustomEvent] Source #

List of counter events configured for the creative. For DISPLAY_IMAGE_GALLERY creatives, these are read-only and auto-generated from clickTags. Applicable to the following creative types: DISPLAY_IMAGE_GALLERY, all RICH_MEDIA, and all VPAID.

creKind :: Lens' Creative Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#creative".

creSSLOverride :: Lens' Creative (Maybe Bool) Source #

Whether creative should be treated as SSL compliant even if the system scan shows it's not. Applicable to all creative types.

creHTMLCode :: Lens' Creative (Maybe Text) Source #

HTML code for the creative. This is a required field when applicable. This field is ignored if htmlCodeLocked is false. Applicable to the following creative types: all CUSTOM, FLASH_INPAGE, and HTML5_BANNER, and all RICH_MEDIA.

creAdvertiserId :: Lens' Creative (Maybe Int64) Source #

Advertiser ID of this creative. This is a required field. Applicable to all creative types.

creRequiredFlashVersion :: Lens' Creative (Maybe Int32) Source #

The internal Flash version for this creative as calculated by DoubleClick Studio. This is a read-only field. Applicable to the following creative types: FLASH_INPAGE all RICH_MEDIA, and all VPAID. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE.

creBackgRoundColor :: Lens' Creative (Maybe Text) Source #

The 6-character HTML color code, beginning with #, for the background of the window area where the Flash file is displayed. Default is white. Applicable to the following creative types: FLASH_INPAGE.

creAdTagKeys :: Lens' Creative [Text] Source #

Keywords for a Rich Media creative. Keywords let you customize the creative settings of a Rich Media ad running on your site without having to contact the advertiser. You can use keywords to dynamically change the look or functionality of a creative. Applicable to the following creative types: all RICH_MEDIA, and all VPAID.

creSkippable :: Lens' Creative (Maybe Bool) Source #

Whether the user can choose to skip the creative. Applicable to the following creative types: all INSTREAM_VIDEO and all VPAID.

creSSLCompliant :: Lens' Creative (Maybe Bool) Source #

Whether the creative is SSL-compliant. This is a read-only field. Applicable to all creative types.

creIdDimensionValue :: Lens' Creative (Maybe DimensionValue) Source #

Dimension value for the ID of this creative. This is a read-only field. Applicable to all creative types.

creBackupImageReportingLabel :: Lens' Creative (Maybe Text) Source #

Reporting label used for HTML5 banner backup image. Applicable to the following creative types: DISPLAY when the primary asset type is not HTML_IMAGE.

creCommercialId :: Lens' Creative (Maybe Text) Source #

Industry standard ID assigned to creative for reach and frequency. Applicable to the following creative types: all INSTREAM_VIDEO and all VPAID.

creActive :: Lens' Creative (Maybe Bool) Source #

Whether the creative is active. Applicable to all creative types.

creExitCustomEvents :: Lens' Creative [CreativeCustomEvent] Source #

List of exit events configured for the creative. For DISPLAY and DISPLAY_IMAGE_GALLERY creatives, these are read-only and auto-generated from clickTags, For DISPLAY, an event is also created from the backupImageReportingLabel. Applicable to the following creative types: DISPLAY_IMAGE_GALLERY, all RICH_MEDIA, and all VPAID. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE.

creAccountId :: Lens' Creative (Maybe Int64) Source #

Account ID of this creative. This field, if left unset, will be auto-generated for both insert and update operations. Applicable to all creative types.

creBackupImageClickThroughURL :: Lens' Creative (Maybe Text) Source #

Click-through URL for backup image. Applicable to the following creative types: FLASH_INPAGE and HTML5_BANNER. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE.

creName :: Lens' Creative (Maybe Text) Source #

Name of the creative. This is a required field and must be less than 256 characters long. Applicable to all creative types.

creOverrideCss :: Lens' Creative (Maybe Text) Source #

Override CSS value for rich media creatives. Applicable to the following creative types: all RICH_MEDIA.

creVideoDescription :: Lens' Creative (Maybe Text) Source #

Description of the video ad. Applicable to the following creative types: all INSTREAM_VIDEO and all VPAID.

creClickTags :: Lens' Creative [ClickTag] Source #

Click tags of the creative. For DISPLAY, FLASH_INPAGE, and HTML5_BANNER creatives, this is a subset of detected click tags for the assets associated with this creative. After creating a flash asset, detected click tags will be returned in the creativeAssetMetadata. When inserting the creative, populate the creative clickTags field using the creativeAssetMetadata.clickTags field. For DISPLAY_IMAGE_GALLERY creatives, there should be exactly one entry in this list for each image creative asset. A click tag is matched with a corresponding creative asset by matching the clickTag.name field with the creativeAsset.assetIdentifier.name field. Applicable to the following creative types: DISPLAY_IMAGE_GALLERY, FLASH_INPAGE, HTML5_BANNER. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE.

creAdParameters :: Lens' Creative (Maybe Text) Source #

Ad parameters user for VPAID creative. This is a read-only field. Applicable to the following creative types: all VPAID.

creVersion :: Lens' Creative (Maybe Int32) Source #

The version number helps you keep track of multiple versions of your creative in your reports. The version number will always be auto-generated during insert operations to start at 1. For tracking creatives the version cannot be incremented and will always remain at 1. For all other creative types the version can be incremented only by 1 during update operations. In addition, the version will be automatically incremented by 1 when undergoing Rich Media creative merging. Applicable to all creative types.

creLatestTraffickedCreativeId :: Lens' Creative (Maybe Int64) Source #

Latest Studio trafficked creative ID associated with rich media and VPAID creatives. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA, and all VPAID.

creThirdPartyRichMediaImpressionsURL :: Lens' Creative (Maybe Text) Source #

Third-party URL used to record rich media impressions. Applicable to the following creative types: all RICH_MEDIA.

creLastModifiedInfo :: Lens' Creative (Maybe LastModifiedInfo) Source #

Creative last modification information. This is a read-only field. Applicable to all creative types.

creId :: Lens' Creative (Maybe Int64) Source #

ID of this creative. This is a read-only, auto-generated field. Applicable to all creative types.

creAuthoringSource :: Lens' Creative (Maybe CreativeAuthoringSource) Source #

Source application where creative was authored. Presently, only DBM authored creatives will have this field set. Applicable to all creative types.

creStudioAdvertiserId :: Lens' Creative (Maybe Int64) Source #

Studio advertiser ID associated with rich media and VPAID creatives. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA, and all VPAID.

creCreativeAssets :: Lens' Creative [CreativeAsset] Source #

Assets associated with a creative. Applicable to all but the following creative types: INTERNAL_REDIRECT, INTERSTITIAL_INTERNAL_REDIRECT, and REDIRECT

creSubAccountId :: Lens' Creative (Maybe Int64) Source #

Subaccount ID of this creative. This field, if left unset, will be auto-generated for both insert and update operations. Applicable to all creative types.

creType :: Lens' Creative (Maybe CreativeType) Source #

Type of this creative.This is a required field. Applicable to all creative types.

creTimerCustomEvents :: Lens' Creative [CreativeCustomEvent] Source #

List of timer events configured for the creative. For DISPLAY_IMAGE_GALLERY creatives, these are read-only and auto-generated from clickTags. Applicable to the following creative types: DISPLAY_IMAGE_GALLERY, all RICH_MEDIA, and all VPAID. Applicable to DISPLAY when the primary asset is not HTML_IMAGE.

creStudioCreativeId :: Lens' Creative (Maybe Int64) Source #

Studio creative ID associated with rich media and VPAID creatives. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA, and all VPAID.

creCompatibility :: Lens' Creative [CreativeCompatibilityItem] Source #

Compatibilities associated with this creative. This is a read-only field. DISPLAY and DISPLAY_INTERSTITIAL refer to rendering either on desktop or on mobile devices or in mobile apps for regular or interstitial ads, respectively. APP and APP_INTERSTITIAL are for rendering in mobile apps. Only pre-existing creatives may have these compatibilities since new creatives will either be assigned DISPLAY or DISPLAY_INTERSTITIAL instead. IN_STREAM_VIDEO refers to rendering in in-stream video ads developed with the VAST standard. Applicable to all creative types. Acceptable values are: - "APP" - "APP_INTERSTITIAL" - "IN_STREAM_VIDEO" - "DISPLAY" - "DISPLAY_INTERSTITIAL"

creBackupImageFeatures :: Lens' Creative [CreativeBackupImageFeaturesItem] Source #

List of feature dependencies that will cause a backup image to be served if the browser that serves the ad does not support them. Feature dependencies are features that a browser must be able to support in order to render your HTML5 creative asset correctly. This field is initially auto-generated to contain all features detected by DCM for all the assets of this creative and can then be modified by the client. To reset this field, copy over all the creativeAssets' detected features. Applicable to the following creative types: HTML5_BANNER. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE.

creArtworkType :: Lens' Creative (Maybe CreativeArtworkType) Source #

Type of artwork used for the creative. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA, and all VPAID.

creArchived :: Lens' Creative (Maybe Bool) Source #

Whether the creative is archived. Applicable to all creative types.

creCompanionCreatives :: Lens' Creative [Int64] Source #

List of companion creatives assigned to an in-Stream videocreative. Acceptable values include IDs of existing flash and image creatives. Applicable to the following creative types: all INSTREAM_VIDEO and all VPAID.

creTotalFileSize :: Lens' Creative (Maybe Int64) Source #

Combined size of all creative assets. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA, and all VPAID.

creStudioTraffickedCreativeId :: Lens' Creative (Maybe Int64) Source #

Studio trafficked creative ID associated with rich media and VPAID creatives. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA, and all VPAID.

creRedirectURL :: Lens' Creative (Maybe Text) Source #

URL of hosted image or hosted video or another ad tag. For INSTREAM_VIDEO_REDIRECT creatives this is the in-stream video redirect URL. The standard for a VAST (Video Ad Serving Template) ad response allows for a redirect link to another VAST 2.0 or 3.0 call. This is a required field when applicable. Applicable to the following creative types: DISPLAY_REDIRECT, INTERNAL_REDIRECT, INTERSTITIAL_INTERNAL_REDIRECT, and INSTREAM_VIDEO_REDIRECT

creAutoAdvanceImages :: Lens' Creative (Maybe Bool) Source #

Whether images are automatically advanced for enhanced image creatives. Applicable to the following creative types: DISPLAY_IMAGE_GALLERY.

creCreativeFieldAssignments :: Lens' Creative [CreativeFieldAssignment] Source #

Creative field assignments for this creative. Applicable to all creative types.

SiteContact

data SiteContact Source #

Site Contact

See: siteContact smart constructor.

Instances

Eq SiteContact Source # 
Data SiteContact Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SiteContact -> c SiteContact #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SiteContact #

toConstr :: SiteContact -> Constr #

dataTypeOf :: SiteContact -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SiteContact) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SiteContact) #

gmapT :: (forall b. Data b => b -> b) -> SiteContact -> SiteContact #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SiteContact -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SiteContact -> r #

gmapQ :: (forall d. Data d => d -> u) -> SiteContact -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SiteContact -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SiteContact -> m SiteContact #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SiteContact -> m SiteContact #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SiteContact -> m SiteContact #

Show SiteContact Source # 
Generic SiteContact Source # 

Associated Types

type Rep SiteContact :: * -> * #

ToJSON SiteContact Source # 
FromJSON SiteContact Source # 
type Rep SiteContact Source # 

siteContact :: SiteContact Source #

Creates a value of SiteContact with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

scEmail :: Lens' SiteContact (Maybe Text) Source #

Email address of this site contact. This is a required field.

scPhone :: Lens' SiteContact (Maybe Text) Source #

Primary phone number of this site contact.

scLastName :: Lens' SiteContact (Maybe Text) Source #

Last name of this site contact.

scAddress :: Lens' SiteContact (Maybe Text) Source #

Address of this site contact.

scFirstName :: Lens' SiteContact (Maybe Text) Source #

First name of this site contact.

scId :: Lens' SiteContact (Maybe Int64) Source #

ID of this site contact. This is a read-only, auto-generated field.

scTitle :: Lens' SiteContact (Maybe Text) Source #

Title or designation of this site contact.

CreativeAuthoringSource

data CreativeAuthoringSource Source #

Source application where creative was authored. Presently, only DBM authored creatives will have this field set. Applicable to all creative types.

Constructors

CreativeAuthoringSourceDBm
CREATIVE_AUTHORING_SOURCE_DBM
CreativeAuthoringSourceDcm
CREATIVE_AUTHORING_SOURCE_DCM
CreativeAuthoringSourceStudio
CREATIVE_AUTHORING_SOURCE_STUDIO

Instances

Enum CreativeAuthoringSource Source # 
Eq CreativeAuthoringSource Source # 
Data CreativeAuthoringSource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAuthoringSource -> c CreativeAuthoringSource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAuthoringSource #

toConstr :: CreativeAuthoringSource -> Constr #

dataTypeOf :: CreativeAuthoringSource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAuthoringSource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAuthoringSource) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAuthoringSource -> CreativeAuthoringSource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAuthoringSource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAuthoringSource -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAuthoringSource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAuthoringSource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAuthoringSource -> m CreativeAuthoringSource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAuthoringSource -> m CreativeAuthoringSource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAuthoringSource -> m CreativeAuthoringSource #

Ord CreativeAuthoringSource Source # 
Read CreativeAuthoringSource Source # 
Show CreativeAuthoringSource Source # 
Generic CreativeAuthoringSource Source # 
Hashable CreativeAuthoringSource Source # 
ToJSON CreativeAuthoringSource Source # 
FromJSON CreativeAuthoringSource Source # 
FromHttpApiData CreativeAuthoringSource Source # 
ToHttpApiData CreativeAuthoringSource Source # 
type Rep CreativeAuthoringSource Source # 
type Rep CreativeAuthoringSource = D1 (MetaData "CreativeAuthoringSource" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CreativeAuthoringSourceDBm" PrefixI False) U1) ((:+:) (C1 (MetaCons "CreativeAuthoringSourceDcm" PrefixI False) U1) (C1 (MetaCons "CreativeAuthoringSourceStudio" PrefixI False) U1)))

AccountsListResponse

data AccountsListResponse Source #

Account List Response

See: accountsListResponse smart constructor.

Instances

Eq AccountsListResponse Source # 
Data AccountsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountsListResponse -> c AccountsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountsListResponse #

toConstr :: AccountsListResponse -> Constr #

dataTypeOf :: AccountsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> AccountsListResponse -> AccountsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountsListResponse -> m AccountsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountsListResponse -> m AccountsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountsListResponse -> m AccountsListResponse #

Show AccountsListResponse Source # 
Generic AccountsListResponse Source # 
ToJSON AccountsListResponse Source # 
FromJSON AccountsListResponse Source # 
type Rep AccountsListResponse Source # 
type Rep AccountsListResponse = D1 (MetaData "AccountsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AccountsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_accNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_accAccounts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Account]))) (S1 (MetaSel (Just Symbol "_accKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

accountsListResponse :: AccountsListResponse Source #

Creates a value of AccountsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

accNextPageToken :: Lens' AccountsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

accKind :: Lens' AccountsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#accountsListResponse".

DateRange

data DateRange Source #

Represents a date range.

See: dateRange smart constructor.

Instances

Eq DateRange Source # 
Data DateRange Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DateRange -> c DateRange #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DateRange #

toConstr :: DateRange -> Constr #

dataTypeOf :: DateRange -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DateRange) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateRange) #

gmapT :: (forall b. Data b => b -> b) -> DateRange -> DateRange #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DateRange -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DateRange -> r #

gmapQ :: (forall d. Data d => d -> u) -> DateRange -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DateRange -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DateRange -> m DateRange #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DateRange -> m DateRange #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DateRange -> m DateRange #

Show DateRange Source # 
Generic DateRange Source # 

Associated Types

type Rep DateRange :: * -> * #

ToJSON DateRange Source # 
FromJSON DateRange Source # 
type Rep DateRange Source # 
type Rep DateRange = D1 (MetaData "DateRange" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DateRange'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_drKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_drEndDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date')))) ((:*:) (S1 (MetaSel (Just Symbol "_drStartDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date'))) (S1 (MetaSel (Just Symbol "_drRelativeDateRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateRangeRelativeDateRange))))))

dateRange :: DateRange Source #

Creates a value of DateRange with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

drKind :: Lens' DateRange Text Source #

The kind of resource this is, in this case dfareporting#dateRange.

drEndDate :: Lens' DateRange (Maybe Day) Source #

The end date of the date range, inclusive. A string of the format: "yyyy-MM-dd".

drStartDate :: Lens' DateRange (Maybe Day) Source #

The start date of the date range, inclusive. A string of the format: "yyyy-MM-dd".

drRelativeDateRange :: Lens' DateRange (Maybe DateRangeRelativeDateRange) Source #

The date range relative to the date of when the report is run.

FloodlightConfigurationStandardVariableTypesItem

data FloodlightConfigurationStandardVariableTypesItem Source #

Constructors

Num
NUM
Ord
ORD
Tran
TRAN
U
U

Instances

Enum FloodlightConfigurationStandardVariableTypesItem Source # 
Eq FloodlightConfigurationStandardVariableTypesItem Source # 
Data FloodlightConfigurationStandardVariableTypesItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightConfigurationStandardVariableTypesItem -> c FloodlightConfigurationStandardVariableTypesItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightConfigurationStandardVariableTypesItem #

toConstr :: FloodlightConfigurationStandardVariableTypesItem -> Constr #

dataTypeOf :: FloodlightConfigurationStandardVariableTypesItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightConfigurationStandardVariableTypesItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightConfigurationStandardVariableTypesItem) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightConfigurationStandardVariableTypesItem -> FloodlightConfigurationStandardVariableTypesItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightConfigurationStandardVariableTypesItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightConfigurationStandardVariableTypesItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightConfigurationStandardVariableTypesItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightConfigurationStandardVariableTypesItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightConfigurationStandardVariableTypesItem -> m FloodlightConfigurationStandardVariableTypesItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightConfigurationStandardVariableTypesItem -> m FloodlightConfigurationStandardVariableTypesItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightConfigurationStandardVariableTypesItem -> m FloodlightConfigurationStandardVariableTypesItem #

Ord FloodlightConfigurationStandardVariableTypesItem Source # 
Read FloodlightConfigurationStandardVariableTypesItem Source # 
Show FloodlightConfigurationStandardVariableTypesItem Source # 
Generic FloodlightConfigurationStandardVariableTypesItem Source # 
Hashable FloodlightConfigurationStandardVariableTypesItem Source # 
ToJSON FloodlightConfigurationStandardVariableTypesItem Source # 
FromJSON FloodlightConfigurationStandardVariableTypesItem Source # 
FromHttpApiData FloodlightConfigurationStandardVariableTypesItem Source # 
ToHttpApiData FloodlightConfigurationStandardVariableTypesItem Source # 
type Rep FloodlightConfigurationStandardVariableTypesItem Source # 
type Rep FloodlightConfigurationStandardVariableTypesItem = D1 (MetaData "FloodlightConfigurationStandardVariableTypesItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "Num" PrefixI False) U1) (C1 (MetaCons "Ord" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Tran" PrefixI False) U1) (C1 (MetaCons "U" PrefixI False) U1)))

Report

data Report Source #

Represents a Report resource.

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 # 
type Rep Report = D1 (MetaData "Report" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Report'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rDelivery") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportDelivery))) (S1 (MetaSel (Just Symbol "_rEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rOwnerProFileId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_rSchedule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportSchedule))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rPathToConversionCriteria") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportPathToConversionCriteria))) (S1 (MetaSel (Just Symbol "_rKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportFormat))) ((:*:) (S1 (MetaSel (Just Symbol "_rReachCriteria") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportReachCriteria))) (S1 (MetaSel (Just Symbol "_rLastModifiedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Word64)))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_rName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_rCrossDimensionReachCriteria") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportCrossDimensionReachCriteria))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportType))) (S1 (MetaSel (Just Symbol "_rSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_rFloodlightCriteria") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportFloodlightCriteria))) ((:*:) (S1 (MetaSel (Just Symbol "_rCriteria") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportCriteria))) (S1 (MetaSel (Just Symbol "_rFileName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))))

rDelivery :: Lens' Report (Maybe ReportDelivery) Source #

The report's email delivery settings.

rEtag :: Lens' Report (Maybe Text) Source #

The eTag of this response for caching purposes.

rOwnerProFileId :: Lens' Report (Maybe Int64) Source #

The user profile id of the owner of this report.

rSchedule :: Lens' Report (Maybe ReportSchedule) Source #

The report's schedule. Can only be set if the report's 'dateRange' is a relative date range and the relative date range is not "TODAY".

rPathToConversionCriteria :: Lens' Report (Maybe ReportPathToConversionCriteria) Source #

The report criteria for a report of type "PATH_TO_CONVERSION".

rKind :: Lens' Report Text Source #

The kind of resource this is, in this case dfareporting#report.

rFormat :: Lens' Report (Maybe ReportFormat) Source #

The output format of the report. If not specified, default format is "CSV". Note that the actual format in the completed report file might differ if for instance the report's size exceeds the format's capabilities. "CSV" will then be the fallback format.

rReachCriteria :: Lens' Report (Maybe ReportReachCriteria) Source #

The report criteria for a report of type "REACH".

rLastModifiedTime :: Lens' Report (Maybe Word64) Source #

The timestamp (in milliseconds since epoch) of when this report was last modified.

rAccountId :: Lens' Report (Maybe Int64) Source #

The account ID to which this report belongs.

rName :: Lens' Report (Maybe Text) Source #

The name of the report.

rId :: Lens' Report (Maybe Int64) Source #

The unique ID identifying this report resource.

rCrossDimensionReachCriteria :: Lens' Report (Maybe ReportCrossDimensionReachCriteria) Source #

The report criteria for a report of type "CROSS_DIMENSION_REACH".

rType :: Lens' Report (Maybe ReportType) Source #

The type of the report.

rSubAccountId :: Lens' Report (Maybe Int64) Source #

The subaccount ID to which this report belongs if applicable.

rFloodlightCriteria :: Lens' Report (Maybe ReportFloodlightCriteria) Source #

The report criteria for a report of type "FLOODLIGHT".

rCriteria :: Lens' Report (Maybe ReportCriteria) Source #

The report criteria for a report of type "STANDARD".

rFileName :: Lens' Report (Maybe Text) Source #

The filename used when generating report files for this report.

PlacementPaymentSource

data PlacementPaymentSource Source #

Payment source for this placement. This is a required field that is read-only after insertion.

Constructors

PPSPlacementAgencyPaid
PLACEMENT_AGENCY_PAID
PPSPlacementPublisherPaid
PLACEMENT_PUBLISHER_PAID

Instances

Enum PlacementPaymentSource Source # 
Eq PlacementPaymentSource Source # 
Data PlacementPaymentSource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementPaymentSource -> c PlacementPaymentSource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementPaymentSource #

toConstr :: PlacementPaymentSource -> Constr #

dataTypeOf :: PlacementPaymentSource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementPaymentSource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementPaymentSource) #

gmapT :: (forall b. Data b => b -> b) -> PlacementPaymentSource -> PlacementPaymentSource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementPaymentSource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementPaymentSource -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementPaymentSource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementPaymentSource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementPaymentSource -> m PlacementPaymentSource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementPaymentSource -> m PlacementPaymentSource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementPaymentSource -> m PlacementPaymentSource #

Ord PlacementPaymentSource Source # 
Read PlacementPaymentSource Source # 
Show PlacementPaymentSource Source # 
Generic PlacementPaymentSource Source # 
Hashable PlacementPaymentSource Source # 
ToJSON PlacementPaymentSource Source # 
FromJSON PlacementPaymentSource Source # 
FromHttpApiData PlacementPaymentSource Source # 
ToHttpApiData PlacementPaymentSource Source # 
type Rep PlacementPaymentSource Source # 
type Rep PlacementPaymentSource = D1 (MetaData "PlacementPaymentSource" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PPSPlacementAgencyPaid" PrefixI False) U1) (C1 (MetaCons "PPSPlacementPublisherPaid" PrefixI False) U1))

ReportsFilesListSortOrder

data ReportsFilesListSortOrder Source #

Order of sorted results, default is 'DESCENDING'.

Constructors

RFLSOAscending

ASCENDING Ascending order.

RFLSODescending

DESCENDING Descending order.

Instances

Enum ReportsFilesListSortOrder Source # 
Eq ReportsFilesListSortOrder Source # 
Data ReportsFilesListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportsFilesListSortOrder -> c ReportsFilesListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportsFilesListSortOrder #

toConstr :: ReportsFilesListSortOrder -> Constr #

dataTypeOf :: ReportsFilesListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportsFilesListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportsFilesListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> ReportsFilesListSortOrder -> ReportsFilesListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportsFilesListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportsFilesListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportsFilesListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportsFilesListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportsFilesListSortOrder -> m ReportsFilesListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportsFilesListSortOrder -> m ReportsFilesListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportsFilesListSortOrder -> m ReportsFilesListSortOrder #

Ord ReportsFilesListSortOrder Source # 
Read ReportsFilesListSortOrder Source # 
Show ReportsFilesListSortOrder Source # 
Generic ReportsFilesListSortOrder Source # 
Hashable ReportsFilesListSortOrder Source # 
ToJSON ReportsFilesListSortOrder Source # 
FromJSON ReportsFilesListSortOrder Source # 
FromHttpApiData ReportsFilesListSortOrder Source # 
ToHttpApiData ReportsFilesListSortOrder Source # 
type Rep ReportsFilesListSortOrder Source # 
type Rep ReportsFilesListSortOrder = D1 (MetaData "ReportsFilesListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "RFLSOAscending" PrefixI False) U1) (C1 (MetaCons "RFLSODescending" PrefixI False) U1))

Campaign

data Campaign Source #

Contains properties of a DCM campaign.

See: campaign smart constructor.

Instances

Eq Campaign Source # 
Data Campaign Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Campaign -> c Campaign #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Campaign #

toConstr :: Campaign -> Constr #

dataTypeOf :: Campaign -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Campaign) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Campaign) #

gmapT :: (forall b. Data b => b -> b) -> Campaign -> Campaign #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Campaign -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Campaign -> r #

gmapQ :: (forall d. Data d => d -> u) -> Campaign -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Campaign -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Campaign -> m Campaign #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Campaign -> m Campaign #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Campaign -> m Campaign #

Show Campaign Source # 
Generic Campaign Source # 

Associated Types

type Rep Campaign :: * -> * #

Methods

from :: Campaign -> Rep Campaign x #

to :: Rep Campaign x -> Campaign #

ToJSON Campaign Source # 
FromJSON Campaign Source # 
type Rep Campaign Source # 
type Rep Campaign = D1 (MetaData "Campaign" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Campaign'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_camCreativeOptimizationConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeOptimizationConfiguration))) ((:*:) (S1 (MetaSel (Just Symbol "_camCreativeGroupIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64]))) (S1 (MetaSel (Just Symbol "_camNielsenOCREnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_camKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_camClickThroughURLSuffixProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ClickThroughURLSuffixProperties)))) ((:*:) (S1 (MetaSel (Just Symbol "_camAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_camEndDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date')))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_camAdvertiserIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) ((:*:) (S1 (MetaSel (Just Symbol "_camIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_camEventTagOverrides") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [EventTagOverride]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_camLookbackConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LookbackConfiguration))) (S1 (MetaSel (Just Symbol "_camStartDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date')))) ((:*:) (S1 (MetaSel (Just Symbol "_camAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_camComscoreVceEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_camName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_camAdvertiserGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_camBillingInvoiceCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_camCreateInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo))) (S1 (MetaSel (Just Symbol "_camLastModifiedInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo)))) ((:*:) (S1 (MetaSel (Just Symbol "_camId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_camSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_camAdditionalCreativeOptimizationConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeOptimizationConfiguration]))) ((:*:) (S1 (MetaSel (Just Symbol "_camExternalId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_camComment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_camAudienceSegmentGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AudienceSegmentGroup]))) (S1 (MetaSel (Just Symbol "_camArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_camTraffickerEmails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_camDefaultClickThroughEventTagProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DefaultClickThroughEventTagProperties)))))))))

camCreativeOptimizationConfiguration :: Lens' Campaign (Maybe CreativeOptimizationConfiguration) Source #

Creative optimization configuration for the campaign.

camCreativeGroupIds :: Lens' Campaign [Int64] Source #

List of creative group IDs that are assigned to the campaign.

camNielsenOCREnabled :: Lens' Campaign (Maybe Bool) Source #

Whether Nielsen reports are enabled for this campaign.

camKind :: Lens' Campaign Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#campaign".

camClickThroughURLSuffixProperties :: Lens' Campaign (Maybe ClickThroughURLSuffixProperties) Source #

Click-through URL suffix override properties for this campaign.

camAdvertiserId :: Lens' Campaign (Maybe Int64) Source #

Advertiser ID of this campaign. This is a required field.

camEndDate :: Lens' Campaign (Maybe Day) Source #

Date on which the campaign will stop running. On insert, the end date must be today or a future date. The end date must be later than or be the same as the start date. If, for example, you set 6/25/2015 as both the start and end dates, the effective campaign run date is just that day only, 6/25/2015. The hours, minutes, and seconds of the end date should not be set, as doing so will result in an error. This is a required field.

camAdvertiserIdDimensionValue :: Lens' Campaign (Maybe DimensionValue) Source #

Dimension value for the advertiser ID of this campaign. This is a read-only, auto-generated field.

camIdDimensionValue :: Lens' Campaign (Maybe DimensionValue) Source #

Dimension value for the ID of this campaign. This is a read-only, auto-generated field.

camEventTagOverrides :: Lens' Campaign [EventTagOverride] Source #

Overrides that can be used to activate or deactivate advertiser event tags.

camLookbackConfiguration :: Lens' Campaign (Maybe LookbackConfiguration) Source #

Lookback window settings for the campaign.

camStartDate :: Lens' Campaign (Maybe Day) Source #

Date on which the campaign starts running. The start date can be any date. The hours, minutes, and seconds of the start date should not be set, as doing so will result in an error. This is a required field.

camAccountId :: Lens' Campaign (Maybe Int64) Source #

Account ID of this campaign. This is a read-only field that can be left blank.

camComscoreVceEnabled :: Lens' Campaign (Maybe Bool) Source #

Whether comScore vCE reports are enabled for this campaign.

camName :: Lens' Campaign (Maybe Text) Source #

Name of this campaign. This is a required field and must be less than 256 characters long and unique among campaigns of the same advertiser.

camAdvertiserGroupId :: Lens' Campaign (Maybe Int64) Source #

Advertiser group ID of the associated advertiser.

camBillingInvoiceCode :: Lens' Campaign (Maybe Text) Source #

Billing invoice code included in the DCM client billing invoices associated with the campaign.

camCreateInfo :: Lens' Campaign (Maybe LastModifiedInfo) Source #

Information about the creation of this campaign. This is a read-only field.

camLastModifiedInfo :: Lens' Campaign (Maybe LastModifiedInfo) Source #

Information about the most recent modification of this campaign. This is a read-only field.

camId :: Lens' Campaign (Maybe Int64) Source #

ID of this campaign. This is a read-only auto-generated field.

camSubAccountId :: Lens' Campaign (Maybe Int64) Source #

Subaccount ID of this campaign. This is a read-only field that can be left blank.

camAdditionalCreativeOptimizationConfigurations :: Lens' Campaign [CreativeOptimizationConfiguration] Source #

Additional creative optimization configurations for the campaign.

camExternalId :: Lens' Campaign (Maybe Text) Source #

External ID for this campaign.

camComment :: Lens' Campaign (Maybe Text) Source #

Arbitrary comments about this campaign. Must be less than 256 characters long.

camAudienceSegmentGroups :: Lens' Campaign [AudienceSegmentGroup] Source #

Audience segment groups assigned to this campaign. Cannot have more than 300 segment groups.

camArchived :: Lens' Campaign (Maybe Bool) Source #

Whether this campaign has been archived.

camTraffickerEmails :: Lens' Campaign [Text] Source #

Campaign trafficker contact emails.

camDefaultClickThroughEventTagProperties :: Lens' Campaign (Maybe DefaultClickThroughEventTagProperties) Source #

Click-through event tag ID override properties for this campaign.

InventoryItemsListSortField

data InventoryItemsListSortField Source #

Field by which to sort the list.

Constructors

IILSFID
ID
IILSFName
NAME

Instances

Enum InventoryItemsListSortField Source # 
Eq InventoryItemsListSortField Source # 
Data InventoryItemsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InventoryItemsListSortField -> c InventoryItemsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InventoryItemsListSortField #

toConstr :: InventoryItemsListSortField -> Constr #

dataTypeOf :: InventoryItemsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InventoryItemsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InventoryItemsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> InventoryItemsListSortField -> InventoryItemsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InventoryItemsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InventoryItemsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> InventoryItemsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InventoryItemsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InventoryItemsListSortField -> m InventoryItemsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryItemsListSortField -> m InventoryItemsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryItemsListSortField -> m InventoryItemsListSortField #

Ord InventoryItemsListSortField Source # 
Read InventoryItemsListSortField Source # 
Show InventoryItemsListSortField Source # 
Generic InventoryItemsListSortField Source # 
Hashable InventoryItemsListSortField Source # 
ToJSON InventoryItemsListSortField Source # 
FromJSON InventoryItemsListSortField Source # 
FromHttpApiData InventoryItemsListSortField Source # 
ToHttpApiData InventoryItemsListSortField Source # 
type Rep InventoryItemsListSortField Source # 
type Rep InventoryItemsListSortField = D1 (MetaData "InventoryItemsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "IILSFID" PrefixI False) U1) (C1 (MetaCons "IILSFName" PrefixI False) U1))

EventTagType

data EventTagType Source #

Event tag type. Can be used to specify whether to use a third-party pixel, a third-party JavaScript URL, or a third-party click-through URL for either impression or click tracking. This is a required field.

Constructors

ETTClickThroughEventTag
CLICK_THROUGH_EVENT_TAG
ETTImpressionImageEventTag
IMPRESSION_IMAGE_EVENT_TAG
ETTImpressionJavascriptEventTag
IMPRESSION_JAVASCRIPT_EVENT_TAG

Instances

Enum EventTagType Source # 
Eq EventTagType Source # 
Data EventTagType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventTagType -> c EventTagType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventTagType #

toConstr :: EventTagType -> Constr #

dataTypeOf :: EventTagType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EventTagType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventTagType) #

gmapT :: (forall b. Data b => b -> b) -> EventTagType -> EventTagType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventTagType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventTagType -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventTagType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventTagType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventTagType -> m EventTagType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTagType -> m EventTagType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTagType -> m EventTagType #

Ord EventTagType Source # 
Read EventTagType Source # 
Show EventTagType Source # 
Generic EventTagType Source # 

Associated Types

type Rep EventTagType :: * -> * #

Hashable EventTagType Source # 
ToJSON EventTagType Source # 
FromJSON EventTagType Source # 
FromHttpApiData EventTagType Source # 
ToHttpApiData EventTagType Source # 
type Rep EventTagType Source # 
type Rep EventTagType = D1 (MetaData "EventTagType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ETTClickThroughEventTag" PrefixI False) U1) ((:+:) (C1 (MetaCons "ETTImpressionImageEventTag" PrefixI False) U1) (C1 (MetaCons "ETTImpressionJavascriptEventTag" PrefixI False) U1)))

CreativesListSortOrder

data CreativesListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

CAscending
ASCENDING
CDescending
DESCENDING

Instances

Enum CreativesListSortOrder Source # 
Eq CreativesListSortOrder Source # 
Data CreativesListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativesListSortOrder -> c CreativesListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativesListSortOrder #

toConstr :: CreativesListSortOrder -> Constr #

dataTypeOf :: CreativesListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativesListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativesListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> CreativesListSortOrder -> CreativesListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativesListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativesListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativesListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativesListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativesListSortOrder -> m CreativesListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativesListSortOrder -> m CreativesListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativesListSortOrder -> m CreativesListSortOrder #

Ord CreativesListSortOrder Source # 
Read CreativesListSortOrder Source # 
Show CreativesListSortOrder Source # 
Generic CreativesListSortOrder Source # 
Hashable CreativesListSortOrder Source # 
ToJSON CreativesListSortOrder Source # 
FromJSON CreativesListSortOrder Source # 
FromHttpApiData CreativesListSortOrder Source # 
ToHttpApiData CreativesListSortOrder Source # 
type Rep CreativesListSortOrder Source # 
type Rep CreativesListSortOrder = D1 (MetaData "CreativesListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CAscending" PrefixI False) U1) (C1 (MetaCons "CDescending" PrefixI False) U1))

InventoryItemsListType

data InventoryItemsListType Source #

Select only inventory items with this type.

Constructors

PlanningPlacementTypeCredit
PLANNING_PLACEMENT_TYPE_CREDIT
PlanningPlacementTypeRegular
PLANNING_PLACEMENT_TYPE_REGULAR

Instances

Enum InventoryItemsListType Source # 
Eq InventoryItemsListType Source # 
Data InventoryItemsListType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InventoryItemsListType -> c InventoryItemsListType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InventoryItemsListType #

toConstr :: InventoryItemsListType -> Constr #

dataTypeOf :: InventoryItemsListType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InventoryItemsListType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InventoryItemsListType) #

gmapT :: (forall b. Data b => b -> b) -> InventoryItemsListType -> InventoryItemsListType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InventoryItemsListType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InventoryItemsListType -> r #

gmapQ :: (forall d. Data d => d -> u) -> InventoryItemsListType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InventoryItemsListType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InventoryItemsListType -> m InventoryItemsListType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryItemsListType -> m InventoryItemsListType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryItemsListType -> m InventoryItemsListType #

Ord InventoryItemsListType Source # 
Read InventoryItemsListType Source # 
Show InventoryItemsListType Source # 
Generic InventoryItemsListType Source # 
Hashable InventoryItemsListType Source # 
ToJSON InventoryItemsListType Source # 
FromJSON InventoryItemsListType Source # 
FromHttpApiData InventoryItemsListType Source # 
ToHttpApiData InventoryItemsListType Source # 
type Rep InventoryItemsListType Source # 
type Rep InventoryItemsListType = D1 (MetaData "InventoryItemsListType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PlanningPlacementTypeCredit" PrefixI False) U1) (C1 (MetaCons "PlanningPlacementTypeRegular" PrefixI False) U1))

ThirdPartyAuthenticationToken

data ThirdPartyAuthenticationToken Source #

Third Party Authentication Token

See: thirdPartyAuthenticationToken smart constructor.

Instances

Eq ThirdPartyAuthenticationToken Source # 
Data ThirdPartyAuthenticationToken Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ThirdPartyAuthenticationToken -> c ThirdPartyAuthenticationToken #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ThirdPartyAuthenticationToken #

toConstr :: ThirdPartyAuthenticationToken -> Constr #

dataTypeOf :: ThirdPartyAuthenticationToken -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ThirdPartyAuthenticationToken) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ThirdPartyAuthenticationToken) #

gmapT :: (forall b. Data b => b -> b) -> ThirdPartyAuthenticationToken -> ThirdPartyAuthenticationToken #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ThirdPartyAuthenticationToken -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ThirdPartyAuthenticationToken -> r #

gmapQ :: (forall d. Data d => d -> u) -> ThirdPartyAuthenticationToken -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ThirdPartyAuthenticationToken -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ThirdPartyAuthenticationToken -> m ThirdPartyAuthenticationToken #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ThirdPartyAuthenticationToken -> m ThirdPartyAuthenticationToken #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ThirdPartyAuthenticationToken -> m ThirdPartyAuthenticationToken #

Show ThirdPartyAuthenticationToken Source # 
Generic ThirdPartyAuthenticationToken Source # 
ToJSON ThirdPartyAuthenticationToken Source # 
FromJSON ThirdPartyAuthenticationToken Source # 
type Rep ThirdPartyAuthenticationToken Source # 
type Rep ThirdPartyAuthenticationToken = D1 (MetaData "ThirdPartyAuthenticationToken" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ThirdPartyAuthenticationToken'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tpatValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tpatName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

thirdPartyAuthenticationToken :: ThirdPartyAuthenticationToken Source #

Creates a value of ThirdPartyAuthenticationToken with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tpatValue :: Lens' ThirdPartyAuthenticationToken (Maybe Text) Source #

Value of the third-party authentication token. This is a read-only, auto-generated field.

tpatName :: Lens' ThirdPartyAuthenticationToken (Maybe Text) Source #

Name of the third-party authentication token.

PopupWindowPropertiesPositionType

data PopupWindowPropertiesPositionType Source #

Popup window position either centered or at specific coordinate.

Constructors

Center
CENTER
Coordinates
COORDINATES

Instances

Enum PopupWindowPropertiesPositionType Source # 
Eq PopupWindowPropertiesPositionType Source # 
Data PopupWindowPropertiesPositionType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PopupWindowPropertiesPositionType -> c PopupWindowPropertiesPositionType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PopupWindowPropertiesPositionType #

toConstr :: PopupWindowPropertiesPositionType -> Constr #

dataTypeOf :: PopupWindowPropertiesPositionType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PopupWindowPropertiesPositionType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PopupWindowPropertiesPositionType) #

gmapT :: (forall b. Data b => b -> b) -> PopupWindowPropertiesPositionType -> PopupWindowPropertiesPositionType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PopupWindowPropertiesPositionType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PopupWindowPropertiesPositionType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PopupWindowPropertiesPositionType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PopupWindowPropertiesPositionType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PopupWindowPropertiesPositionType -> m PopupWindowPropertiesPositionType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PopupWindowPropertiesPositionType -> m PopupWindowPropertiesPositionType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PopupWindowPropertiesPositionType -> m PopupWindowPropertiesPositionType #

Ord PopupWindowPropertiesPositionType Source # 
Read PopupWindowPropertiesPositionType Source # 
Show PopupWindowPropertiesPositionType Source # 
Generic PopupWindowPropertiesPositionType Source # 
Hashable PopupWindowPropertiesPositionType Source # 
ToJSON PopupWindowPropertiesPositionType Source # 
FromJSON PopupWindowPropertiesPositionType Source # 
FromHttpApiData PopupWindowPropertiesPositionType Source # 
ToHttpApiData PopupWindowPropertiesPositionType Source # 
type Rep PopupWindowPropertiesPositionType Source # 
type Rep PopupWindowPropertiesPositionType = D1 (MetaData "PopupWindowPropertiesPositionType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Center" PrefixI False) U1) (C1 (MetaCons "Coordinates" PrefixI False) U1))

DirectorySiteContactRole

data DirectorySiteContactRole Source #

Directory site contact role.

Constructors

Admin
ADMIN
Edit
EDIT
View
VIEW

Instances

Enum DirectorySiteContactRole Source # 
Eq DirectorySiteContactRole Source # 
Data DirectorySiteContactRole Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectorySiteContactRole -> c DirectorySiteContactRole #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectorySiteContactRole #

toConstr :: DirectorySiteContactRole -> Constr #

dataTypeOf :: DirectorySiteContactRole -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectorySiteContactRole) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectorySiteContactRole) #

gmapT :: (forall b. Data b => b -> b) -> DirectorySiteContactRole -> DirectorySiteContactRole #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteContactRole -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteContactRole -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectorySiteContactRole -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectorySiteContactRole -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectorySiteContactRole -> m DirectorySiteContactRole #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteContactRole -> m DirectorySiteContactRole #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteContactRole -> m DirectorySiteContactRole #

Ord DirectorySiteContactRole Source # 
Read DirectorySiteContactRole Source # 
Show DirectorySiteContactRole Source # 
Generic DirectorySiteContactRole Source # 
Hashable DirectorySiteContactRole Source # 
ToJSON DirectorySiteContactRole Source # 
FromJSON DirectorySiteContactRole Source # 
FromHttpApiData DirectorySiteContactRole Source # 
ToHttpApiData DirectorySiteContactRole Source # 
type Rep DirectorySiteContactRole Source # 
type Rep DirectorySiteContactRole = D1 (MetaData "DirectorySiteContactRole" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Admin" PrefixI False) U1) ((:+:) (C1 (MetaCons "Edit" PrefixI False) U1) (C1 (MetaCons "View" PrefixI False) U1)))

ClickThroughURL

data ClickThroughURL Source #

Click-through URL

See: clickThroughURL smart constructor.

Instances

Eq ClickThroughURL Source # 
Data ClickThroughURL Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClickThroughURL -> c ClickThroughURL #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClickThroughURL #

toConstr :: ClickThroughURL -> Constr #

dataTypeOf :: ClickThroughURL -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ClickThroughURL) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClickThroughURL) #

gmapT :: (forall b. Data b => b -> b) -> ClickThroughURL -> ClickThroughURL #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClickThroughURL -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClickThroughURL -> r #

gmapQ :: (forall d. Data d => d -> u) -> ClickThroughURL -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClickThroughURL -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClickThroughURL -> m ClickThroughURL #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClickThroughURL -> m ClickThroughURL #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClickThroughURL -> m ClickThroughURL #

Show ClickThroughURL Source # 
Generic ClickThroughURL Source # 
ToJSON ClickThroughURL Source # 
FromJSON ClickThroughURL Source # 
type Rep ClickThroughURL Source # 
type Rep ClickThroughURL = D1 (MetaData "ClickThroughURL" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ClickThroughURL'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ctuDefaultLandingPage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_ctuComputedClickThroughURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ctuCustomClickThroughURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ctuLandingPageId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

clickThroughURL :: ClickThroughURL Source #

Creates a value of ClickThroughURL with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ctuDefaultLandingPage :: Lens' ClickThroughURL (Maybe Bool) Source #

Whether the campaign default landing page is used.

ctuComputedClickThroughURL :: Lens' ClickThroughURL (Maybe Text) Source #

Read-only convenience field representing the actual URL that will be used for this click-through. The URL is computed as follows: - If defaultLandingPage is enabled then the campaign's default landing page URL is assigned to this field. - If defaultLandingPage is not enabled and a landingPageId is specified then that landing page's URL is assigned to this field. - If neither of the above cases apply, then the customClickThroughUrl is assigned to this field.

ctuCustomClickThroughURL :: Lens' ClickThroughURL (Maybe Text) Source #

Custom click-through URL. Applicable if the defaultLandingPage field is set to false and the landingPageId field is left unset.

ctuLandingPageId :: Lens' ClickThroughURL (Maybe Int64) Source #

ID of the landing page for the click-through URL. Applicable if the defaultLandingPage field is set to false.

TagSettingKeywordOption

data TagSettingKeywordOption Source #

Option specifying how keywords are embedded in ad tags. This setting can be used to specify whether keyword placeholders are inserted in placement tags for this site. Publishers can then add keywords to those placeholders.

Constructors

GenerateSeparateTagForEachKeyword
GENERATE_SEPARATE_TAG_FOR_EACH_KEYWORD
Ignore
IGNORE
PlaceholderWithListOfKeywords
PLACEHOLDER_WITH_LIST_OF_KEYWORDS

Instances

Enum TagSettingKeywordOption Source # 
Eq TagSettingKeywordOption Source # 
Data TagSettingKeywordOption Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TagSettingKeywordOption -> c TagSettingKeywordOption #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TagSettingKeywordOption #

toConstr :: TagSettingKeywordOption -> Constr #

dataTypeOf :: TagSettingKeywordOption -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TagSettingKeywordOption) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TagSettingKeywordOption) #

gmapT :: (forall b. Data b => b -> b) -> TagSettingKeywordOption -> TagSettingKeywordOption #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TagSettingKeywordOption -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TagSettingKeywordOption -> r #

gmapQ :: (forall d. Data d => d -> u) -> TagSettingKeywordOption -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TagSettingKeywordOption -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TagSettingKeywordOption -> m TagSettingKeywordOption #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TagSettingKeywordOption -> m TagSettingKeywordOption #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TagSettingKeywordOption -> m TagSettingKeywordOption #

Ord TagSettingKeywordOption Source # 
Read TagSettingKeywordOption Source # 
Show TagSettingKeywordOption Source # 
Generic TagSettingKeywordOption Source # 
Hashable TagSettingKeywordOption Source # 
ToJSON TagSettingKeywordOption Source # 
FromJSON TagSettingKeywordOption Source # 
FromHttpApiData TagSettingKeywordOption Source # 
ToHttpApiData TagSettingKeywordOption Source # 
type Rep TagSettingKeywordOption Source # 
type Rep TagSettingKeywordOption = D1 (MetaData "TagSettingKeywordOption" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "GenerateSeparateTagForEachKeyword" PrefixI False) U1) ((:+:) (C1 (MetaCons "Ignore" PrefixI False) U1) (C1 (MetaCons "PlaceholderWithListOfKeywords" PrefixI False) U1)))

CreativeAuthoringTool

data CreativeAuthoringTool Source #

Authoring tool for HTML5 banner creatives. This is a read-only field. Applicable to the following creative types: HTML5_BANNER.

Constructors

Ninja
NINJA
Swiffy
SWIFFY

Instances

Enum CreativeAuthoringTool Source # 
Eq CreativeAuthoringTool Source # 
Data CreativeAuthoringTool Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAuthoringTool -> c CreativeAuthoringTool #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAuthoringTool #

toConstr :: CreativeAuthoringTool -> Constr #

dataTypeOf :: CreativeAuthoringTool -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAuthoringTool) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAuthoringTool) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAuthoringTool -> CreativeAuthoringTool #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAuthoringTool -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAuthoringTool -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAuthoringTool -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAuthoringTool -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAuthoringTool -> m CreativeAuthoringTool #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAuthoringTool -> m CreativeAuthoringTool #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAuthoringTool -> m CreativeAuthoringTool #

Ord CreativeAuthoringTool Source # 
Read CreativeAuthoringTool Source # 
Show CreativeAuthoringTool Source # 
Generic CreativeAuthoringTool Source # 
Hashable CreativeAuthoringTool Source # 
ToJSON CreativeAuthoringTool Source # 
FromJSON CreativeAuthoringTool Source # 
FromHttpApiData CreativeAuthoringTool Source # 
ToHttpApiData CreativeAuthoringTool Source # 
type Rep CreativeAuthoringTool Source # 
type Rep CreativeAuthoringTool = D1 (MetaData "CreativeAuthoringTool" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Ninja" PrefixI False) U1) (C1 (MetaCons "Swiffy" PrefixI False) U1))

OrderContactContactType

data OrderContactContactType Source #

Type of this contact.

Constructors

PlanningOrderContactBuyerBillingContact
PLANNING_ORDER_CONTACT_BUYER_BILLING_CONTACT
PlanningOrderContactBuyerContact
PLANNING_ORDER_CONTACT_BUYER_CONTACT
PlanningOrderContactSellerContact
PLANNING_ORDER_CONTACT_SELLER_CONTACT

Instances

Enum OrderContactContactType Source # 
Eq OrderContactContactType Source # 
Data OrderContactContactType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderContactContactType -> c OrderContactContactType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderContactContactType #

toConstr :: OrderContactContactType -> Constr #

dataTypeOf :: OrderContactContactType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderContactContactType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderContactContactType) #

gmapT :: (forall b. Data b => b -> b) -> OrderContactContactType -> OrderContactContactType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderContactContactType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderContactContactType -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderContactContactType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderContactContactType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderContactContactType -> m OrderContactContactType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderContactContactType -> m OrderContactContactType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderContactContactType -> m OrderContactContactType #

Ord OrderContactContactType Source # 
Read OrderContactContactType Source # 
Show OrderContactContactType Source # 
Generic OrderContactContactType Source # 
Hashable OrderContactContactType Source # 
ToJSON OrderContactContactType Source # 
FromJSON OrderContactContactType Source # 
FromHttpApiData OrderContactContactType Source # 
ToHttpApiData OrderContactContactType Source # 
type Rep OrderContactContactType Source # 
type Rep OrderContactContactType = D1 (MetaData "OrderContactContactType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PlanningOrderContactBuyerBillingContact" PrefixI False) U1) ((:+:) (C1 (MetaCons "PlanningOrderContactBuyerContact" PrefixI False) U1) (C1 (MetaCons "PlanningOrderContactSellerContact" PrefixI False) U1)))

CreativeAssetIdType

data CreativeAssetIdType Source #

Type of asset to upload. This is a required field. IMAGE is solely used for IMAGE creatives. Other image assets should use HTML_IMAGE.

Constructors

CAITFlash
FLASH
CAITHTML
HTML
CAITHTMLImage
HTML_IMAGE
CAITImage
IMAGE
CAITVideo
VIDEO

Instances

Enum CreativeAssetIdType Source # 
Eq CreativeAssetIdType Source # 
Data CreativeAssetIdType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetIdType -> c CreativeAssetIdType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetIdType #

toConstr :: CreativeAssetIdType -> Constr #

dataTypeOf :: CreativeAssetIdType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetIdType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetIdType) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetIdType -> CreativeAssetIdType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetIdType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetIdType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetIdType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetIdType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetIdType -> m CreativeAssetIdType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetIdType -> m CreativeAssetIdType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetIdType -> m CreativeAssetIdType #

Ord CreativeAssetIdType Source # 
Read CreativeAssetIdType Source # 
Show CreativeAssetIdType Source # 
Generic CreativeAssetIdType Source # 
Hashable CreativeAssetIdType Source # 
ToJSON CreativeAssetIdType Source # 
FromJSON CreativeAssetIdType Source # 
FromHttpApiData CreativeAssetIdType Source # 
ToHttpApiData CreativeAssetIdType Source # 
type Rep CreativeAssetIdType Source # 
type Rep CreativeAssetIdType = D1 (MetaData "CreativeAssetIdType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "CAITFlash" PrefixI False) U1) (C1 (MetaCons "CAITHTML" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CAITHTMLImage" PrefixI False) U1) ((:+:) (C1 (MetaCons "CAITImage" PrefixI False) U1) (C1 (MetaCons "CAITVideo" PrefixI False) U1))))

AccountUserProFilesListSortOrder

data AccountUserProFilesListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

AUPFLSOAscending
ASCENDING
AUPFLSODescending
DESCENDING

Instances

Enum AccountUserProFilesListSortOrder Source # 
Eq AccountUserProFilesListSortOrder Source # 
Data AccountUserProFilesListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountUserProFilesListSortOrder -> c AccountUserProFilesListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountUserProFilesListSortOrder #

toConstr :: AccountUserProFilesListSortOrder -> Constr #

dataTypeOf :: AccountUserProFilesListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountUserProFilesListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountUserProFilesListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> AccountUserProFilesListSortOrder -> AccountUserProFilesListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountUserProFilesListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountUserProFilesListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountUserProFilesListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountUserProFilesListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountUserProFilesListSortOrder -> m AccountUserProFilesListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountUserProFilesListSortOrder -> m AccountUserProFilesListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountUserProFilesListSortOrder -> m AccountUserProFilesListSortOrder #

Ord AccountUserProFilesListSortOrder Source # 
Read AccountUserProFilesListSortOrder Source # 
Show AccountUserProFilesListSortOrder Source # 
Generic AccountUserProFilesListSortOrder Source # 
Hashable AccountUserProFilesListSortOrder Source # 
ToJSON AccountUserProFilesListSortOrder Source # 
FromJSON AccountUserProFilesListSortOrder Source # 
FromHttpApiData AccountUserProFilesListSortOrder Source # 
ToHttpApiData AccountUserProFilesListSortOrder Source # 
type Rep AccountUserProFilesListSortOrder Source # 
type Rep AccountUserProFilesListSortOrder = D1 (MetaData "AccountUserProFilesListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "AUPFLSOAscending" PrefixI False) U1) (C1 (MetaCons "AUPFLSODescending" PrefixI False) U1))

RemarketingListListSource

data RemarketingListListSource Source #

Product from which this remarketing list was originated.

Constructors

RLLSRemarketingListSourceAdx
REMARKETING_LIST_SOURCE_ADX
RLLSRemarketingListSourceDBm
REMARKETING_LIST_SOURCE_DBM
RLLSRemarketingListSourceDfa
REMARKETING_LIST_SOURCE_DFA
RLLSRemarketingListSourceDfp
REMARKETING_LIST_SOURCE_DFP
RLLSRemarketingListSourceDmp
REMARKETING_LIST_SOURCE_DMP
RLLSRemarketingListSourceGa
REMARKETING_LIST_SOURCE_GA
RLLSRemarketingListSourceGplus
REMARKETING_LIST_SOURCE_GPLUS
RLLSRemarketingListSourceOther
REMARKETING_LIST_SOURCE_OTHER
RLLSRemarketingListSourcePlayStore
REMARKETING_LIST_SOURCE_PLAY_STORE
RLLSRemarketingListSourceXfp
REMARKETING_LIST_SOURCE_XFP
RLLSRemarketingListSourceYouTube
REMARKETING_LIST_SOURCE_YOUTUBE

Instances

Enum RemarketingListListSource Source # 
Eq RemarketingListListSource Source # 
Data RemarketingListListSource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RemarketingListListSource -> c RemarketingListListSource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RemarketingListListSource #

toConstr :: RemarketingListListSource -> Constr #

dataTypeOf :: RemarketingListListSource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RemarketingListListSource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RemarketingListListSource) #

gmapT :: (forall b. Data b => b -> b) -> RemarketingListListSource -> RemarketingListListSource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RemarketingListListSource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RemarketingListListSource -> r #

gmapQ :: (forall d. Data d => d -> u) -> RemarketingListListSource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RemarketingListListSource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RemarketingListListSource -> m RemarketingListListSource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RemarketingListListSource -> m RemarketingListListSource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RemarketingListListSource -> m RemarketingListListSource #

Ord RemarketingListListSource Source # 
Read RemarketingListListSource Source # 
Show RemarketingListListSource Source # 
Generic RemarketingListListSource Source # 
Hashable RemarketingListListSource Source # 
ToJSON RemarketingListListSource Source # 
FromJSON RemarketingListListSource Source # 
FromHttpApiData RemarketingListListSource Source # 
ToHttpApiData RemarketingListListSource Source # 
type Rep RemarketingListListSource Source # 
type Rep RemarketingListListSource = D1 (MetaData "RemarketingListListSource" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "RLLSRemarketingListSourceAdx" PrefixI False) U1) (C1 (MetaCons "RLLSRemarketingListSourceDBm" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RLLSRemarketingListSourceDfa" PrefixI False) U1) ((:+:) (C1 (MetaCons "RLLSRemarketingListSourceDfp" PrefixI False) U1) (C1 (MetaCons "RLLSRemarketingListSourceDmp" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "RLLSRemarketingListSourceGa" PrefixI False) U1) ((:+:) (C1 (MetaCons "RLLSRemarketingListSourceGplus" PrefixI False) U1) (C1 (MetaCons "RLLSRemarketingListSourceOther" PrefixI False) U1))) ((:+:) (C1 (MetaCons "RLLSRemarketingListSourcePlayStore" PrefixI False) U1) ((:+:) (C1 (MetaCons "RLLSRemarketingListSourceXfp" PrefixI False) U1) (C1 (MetaCons "RLLSRemarketingListSourceYouTube" PrefixI False) U1)))))

BrowsersListResponse

data BrowsersListResponse Source #

Browser List Response

See: browsersListResponse smart constructor.

Instances

Eq BrowsersListResponse Source # 
Data BrowsersListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BrowsersListResponse -> c BrowsersListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BrowsersListResponse #

toConstr :: BrowsersListResponse -> Constr #

dataTypeOf :: BrowsersListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BrowsersListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BrowsersListResponse) #

gmapT :: (forall b. Data b => b -> b) -> BrowsersListResponse -> BrowsersListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BrowsersListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BrowsersListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> BrowsersListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BrowsersListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BrowsersListResponse -> m BrowsersListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BrowsersListResponse -> m BrowsersListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BrowsersListResponse -> m BrowsersListResponse #

Show BrowsersListResponse Source # 
Generic BrowsersListResponse Source # 
ToJSON BrowsersListResponse Source # 
FromJSON BrowsersListResponse Source # 
type Rep BrowsersListResponse Source # 
type Rep BrowsersListResponse = D1 (MetaData "BrowsersListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "BrowsersListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_blrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_blrBrowsers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Browser])))))

browsersListResponse :: BrowsersListResponse Source #

Creates a value of BrowsersListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

blrKind :: Lens' BrowsersListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#browsersListResponse".

AccountUserProFileUserAccessType

data AccountUserProFileUserAccessType Source #

User type of the user profile. This is a read-only field that can be left blank.

Constructors

InternalAdministrator
INTERNAL_ADMINISTRATOR
NormalUser
NORMAL_USER
ReadOnlySuperUser
READ_ONLY_SUPER_USER
SuperUser
SUPER_USER

Instances

Enum AccountUserProFileUserAccessType Source # 
Eq AccountUserProFileUserAccessType Source # 
Data AccountUserProFileUserAccessType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountUserProFileUserAccessType -> c AccountUserProFileUserAccessType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountUserProFileUserAccessType #

toConstr :: AccountUserProFileUserAccessType -> Constr #

dataTypeOf :: AccountUserProFileUserAccessType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountUserProFileUserAccessType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountUserProFileUserAccessType) #

gmapT :: (forall b. Data b => b -> b) -> AccountUserProFileUserAccessType -> AccountUserProFileUserAccessType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountUserProFileUserAccessType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountUserProFileUserAccessType -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountUserProFileUserAccessType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountUserProFileUserAccessType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountUserProFileUserAccessType -> m AccountUserProFileUserAccessType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountUserProFileUserAccessType -> m AccountUserProFileUserAccessType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountUserProFileUserAccessType -> m AccountUserProFileUserAccessType #

Ord AccountUserProFileUserAccessType Source # 
Read AccountUserProFileUserAccessType Source # 
Show AccountUserProFileUserAccessType Source # 
Generic AccountUserProFileUserAccessType Source # 
Hashable AccountUserProFileUserAccessType Source # 
ToJSON AccountUserProFileUserAccessType Source # 
FromJSON AccountUserProFileUserAccessType Source # 
FromHttpApiData AccountUserProFileUserAccessType Source # 
ToHttpApiData AccountUserProFileUserAccessType Source # 
type Rep AccountUserProFileUserAccessType Source # 
type Rep AccountUserProFileUserAccessType = D1 (MetaData "AccountUserProFileUserAccessType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "InternalAdministrator" PrefixI False) U1) (C1 (MetaCons "NormalUser" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ReadOnlySuperUser" PrefixI False) U1) (C1 (MetaCons "SuperUser" PrefixI False) U1)))

CreativeAssetStartTimeType

data CreativeAssetStartTimeType Source #

Initial wait time type before making the asset visible. Applicable to the following creative types: all RICH_MEDIA.

Constructors

AssetStartTimeTypeCustom
ASSET_START_TIME_TYPE_CUSTOM
AssetStartTimeTypeNone
ASSET_START_TIME_TYPE_NONE

Instances

Enum CreativeAssetStartTimeType Source # 
Eq CreativeAssetStartTimeType Source # 
Data CreativeAssetStartTimeType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetStartTimeType -> c CreativeAssetStartTimeType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetStartTimeType #

toConstr :: CreativeAssetStartTimeType -> Constr #

dataTypeOf :: CreativeAssetStartTimeType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetStartTimeType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetStartTimeType) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetStartTimeType -> CreativeAssetStartTimeType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetStartTimeType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetStartTimeType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetStartTimeType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetStartTimeType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetStartTimeType -> m CreativeAssetStartTimeType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetStartTimeType -> m CreativeAssetStartTimeType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetStartTimeType -> m CreativeAssetStartTimeType #

Ord CreativeAssetStartTimeType Source # 
Read CreativeAssetStartTimeType Source # 
Show CreativeAssetStartTimeType Source # 
Generic CreativeAssetStartTimeType Source # 
Hashable CreativeAssetStartTimeType Source # 
ToJSON CreativeAssetStartTimeType Source # 
FromJSON CreativeAssetStartTimeType Source # 
FromHttpApiData CreativeAssetStartTimeType Source # 
ToHttpApiData CreativeAssetStartTimeType Source # 
type Rep CreativeAssetStartTimeType Source # 
type Rep CreativeAssetStartTimeType = D1 (MetaData "CreativeAssetStartTimeType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "AssetStartTimeTypeCustom" PrefixI False) U1) (C1 (MetaCons "AssetStartTimeTypeNone" PrefixI False) U1))

ProjectAudienceGender

data ProjectAudienceGender Source #

Audience gender of this project.

Constructors

PlanningAudienceGenderFemale
PLANNING_AUDIENCE_GENDER_FEMALE
PlanningAudienceGenderMale
PLANNING_AUDIENCE_GENDER_MALE

Instances

Enum ProjectAudienceGender Source # 
Eq ProjectAudienceGender Source # 
Data ProjectAudienceGender Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProjectAudienceGender -> c ProjectAudienceGender #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProjectAudienceGender #

toConstr :: ProjectAudienceGender -> Constr #

dataTypeOf :: ProjectAudienceGender -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProjectAudienceGender) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProjectAudienceGender) #

gmapT :: (forall b. Data b => b -> b) -> ProjectAudienceGender -> ProjectAudienceGender #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProjectAudienceGender -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProjectAudienceGender -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProjectAudienceGender -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProjectAudienceGender -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProjectAudienceGender -> m ProjectAudienceGender #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProjectAudienceGender -> m ProjectAudienceGender #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProjectAudienceGender -> m ProjectAudienceGender #

Ord ProjectAudienceGender Source # 
Read ProjectAudienceGender Source # 
Show ProjectAudienceGender Source # 
Generic ProjectAudienceGender Source # 
Hashable ProjectAudienceGender Source # 
ToJSON ProjectAudienceGender Source # 
FromJSON ProjectAudienceGender Source # 
FromHttpApiData ProjectAudienceGender Source # 
ToHttpApiData ProjectAudienceGender Source # 
type Rep ProjectAudienceGender Source # 
type Rep ProjectAudienceGender = D1 (MetaData "ProjectAudienceGender" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PlanningAudienceGenderFemale" PrefixI False) U1) (C1 (MetaCons "PlanningAudienceGenderMale" PrefixI False) U1))

SiteSettings

data SiteSettings Source #

Site Settings

See: siteSettings smart constructor.

Instances

Eq SiteSettings Source # 
Data SiteSettings Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SiteSettings -> c SiteSettings #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SiteSettings #

toConstr :: SiteSettings -> Constr #

dataTypeOf :: SiteSettings -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SiteSettings) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SiteSettings) #

gmapT :: (forall b. Data b => b -> b) -> SiteSettings -> SiteSettings #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SiteSettings -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SiteSettings -> r #

gmapQ :: (forall d. Data d => d -> u) -> SiteSettings -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SiteSettings -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SiteSettings -> m SiteSettings #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SiteSettings -> m SiteSettings #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SiteSettings -> m SiteSettings #

Show SiteSettings Source # 
Generic SiteSettings Source # 

Associated Types

type Rep SiteSettings :: * -> * #

ToJSON SiteSettings Source # 
FromJSON SiteSettings Source # 
type Rep SiteSettings Source # 
type Rep SiteSettings = D1 (MetaData "SiteSettings" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "SiteSettings'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ssDisableNewCookie") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_ssDisableBrandSafeAds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_ssLookbackConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LookbackConfiguration))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ssTagSetting") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TagSetting))) (S1 (MetaSel (Just Symbol "_ssActiveViewOptOut") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_ssVideoActiveViewOptOut") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_ssCreativeSettings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeSettings)))))))

siteSettings :: SiteSettings Source #

Creates a value of SiteSettings with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ssDisableNewCookie :: Lens' SiteSettings (Maybe Bool) Source #

Whether new cookies are disabled for this site.

ssDisableBrandSafeAds :: Lens' SiteSettings (Maybe Bool) Source #

Whether brand safe ads are disabled for this site.

ssLookbackConfiguration :: Lens' SiteSettings (Maybe LookbackConfiguration) Source #

Lookback window settings for this site.

ssTagSetting :: Lens' SiteSettings (Maybe TagSetting) Source #

Configuration settings for dynamic and image floodlight tags.

ssActiveViewOptOut :: Lens' SiteSettings (Maybe Bool) Source #

Whether active view creatives are disabled for this site.

ssVideoActiveViewOptOut :: Lens' SiteSettings (Maybe Bool) Source #

Whether Verification and ActiveView are disabled for in-stream video creatives on this site. The same setting videoActiveViewOptOut exists on the directory site level -- the opt out occurs if either of these settings are true. These settings are distinct from DirectorySites.settings.activeViewOptOut or Sites.siteSettings.activeViewOptOut which only apply to display ads. However, Accounts.activeViewOptOut opts out both video traffic, as well as display ads, from Verification and ActiveView.

PlacementStrategiesListSortField

data PlacementStrategiesListSortField Source #

Field by which to sort the list.

Constructors

PSLSFID
ID
PSLSFName
NAME

Instances

Enum PlacementStrategiesListSortField Source # 
Eq PlacementStrategiesListSortField Source # 
Data PlacementStrategiesListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementStrategiesListSortField -> c PlacementStrategiesListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementStrategiesListSortField #

toConstr :: PlacementStrategiesListSortField -> Constr #

dataTypeOf :: PlacementStrategiesListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementStrategiesListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementStrategiesListSortField) #

gmapT :: (forall b. Data b => b -> b) -> PlacementStrategiesListSortField -> PlacementStrategiesListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementStrategiesListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementStrategiesListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementStrategiesListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementStrategiesListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementStrategiesListSortField -> m PlacementStrategiesListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementStrategiesListSortField -> m PlacementStrategiesListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementStrategiesListSortField -> m PlacementStrategiesListSortField #

Ord PlacementStrategiesListSortField Source # 
Read PlacementStrategiesListSortField Source # 
Show PlacementStrategiesListSortField Source # 
Generic PlacementStrategiesListSortField Source # 
Hashable PlacementStrategiesListSortField Source # 
ToJSON PlacementStrategiesListSortField Source # 
FromJSON PlacementStrategiesListSortField Source # 
FromHttpApiData PlacementStrategiesListSortField Source # 
ToHttpApiData PlacementStrategiesListSortField Source # 
type Rep PlacementStrategiesListSortField Source # 
type Rep PlacementStrategiesListSortField = D1 (MetaData "PlacementStrategiesListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PSLSFID" PrefixI False) U1) (C1 (MetaCons "PSLSFName" PrefixI False) U1))

ContentCategoriesListResponse

data ContentCategoriesListResponse Source #

Content Category List Response

See: contentCategoriesListResponse smart constructor.

Instances

Eq ContentCategoriesListResponse Source # 
Data ContentCategoriesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ContentCategoriesListResponse -> c ContentCategoriesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ContentCategoriesListResponse #

toConstr :: ContentCategoriesListResponse -> Constr #

dataTypeOf :: ContentCategoriesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ContentCategoriesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ContentCategoriesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> ContentCategoriesListResponse -> ContentCategoriesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ContentCategoriesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ContentCategoriesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ContentCategoriesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ContentCategoriesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ContentCategoriesListResponse -> m ContentCategoriesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ContentCategoriesListResponse -> m ContentCategoriesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ContentCategoriesListResponse -> m ContentCategoriesListResponse #

Show ContentCategoriesListResponse Source # 
Generic ContentCategoriesListResponse Source # 
ToJSON ContentCategoriesListResponse Source # 
FromJSON ContentCategoriesListResponse Source # 
type Rep ContentCategoriesListResponse Source # 
type Rep ContentCategoriesListResponse = D1 (MetaData "ContentCategoriesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ContentCategoriesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cclrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cclrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_cclrContentCategories") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ContentCategory]))))))

contentCategoriesListResponse :: ContentCategoriesListResponse Source #

Creates a value of ContentCategoriesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cclrNextPageToken :: Lens' ContentCategoriesListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

cclrKind :: Lens' ContentCategoriesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#contentCategoriesListResponse".

UserDefinedVariableConfigurationDataType

data UserDefinedVariableConfigurationDataType Source #

Data type for the variable. This is a required field.

Constructors

Number
NUMBER
String
STRING

Instances

Enum UserDefinedVariableConfigurationDataType Source # 
Eq UserDefinedVariableConfigurationDataType Source # 
Data UserDefinedVariableConfigurationDataType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserDefinedVariableConfigurationDataType -> c UserDefinedVariableConfigurationDataType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserDefinedVariableConfigurationDataType #

toConstr :: UserDefinedVariableConfigurationDataType -> Constr #

dataTypeOf :: UserDefinedVariableConfigurationDataType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserDefinedVariableConfigurationDataType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserDefinedVariableConfigurationDataType) #

gmapT :: (forall b. Data b => b -> b) -> UserDefinedVariableConfigurationDataType -> UserDefinedVariableConfigurationDataType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserDefinedVariableConfigurationDataType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserDefinedVariableConfigurationDataType -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserDefinedVariableConfigurationDataType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserDefinedVariableConfigurationDataType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserDefinedVariableConfigurationDataType -> m UserDefinedVariableConfigurationDataType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserDefinedVariableConfigurationDataType -> m UserDefinedVariableConfigurationDataType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserDefinedVariableConfigurationDataType -> m UserDefinedVariableConfigurationDataType #

Ord UserDefinedVariableConfigurationDataType Source # 
Read UserDefinedVariableConfigurationDataType Source # 
Show UserDefinedVariableConfigurationDataType Source # 
Generic UserDefinedVariableConfigurationDataType Source # 
Hashable UserDefinedVariableConfigurationDataType Source # 
ToJSON UserDefinedVariableConfigurationDataType Source # 
FromJSON UserDefinedVariableConfigurationDataType Source # 
FromHttpApiData UserDefinedVariableConfigurationDataType Source # 
ToHttpApiData UserDefinedVariableConfigurationDataType Source # 
type Rep UserDefinedVariableConfigurationDataType Source # 
type Rep UserDefinedVariableConfigurationDataType = D1 (MetaData "UserDefinedVariableConfigurationDataType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Number" PrefixI False) U1) (C1 (MetaCons "String" PrefixI False) U1))

FloodlightActivityCacheBustingType

data FloodlightActivityCacheBustingType Source #

Code type used for cache busting in the generated tag.

Constructors

ActiveServerPage
ACTIVE_SERVER_PAGE
ColdFusion
COLD_FUSION
Javascript
JAVASCRIPT
Jsp
JSP
Php
PHP

Instances

Enum FloodlightActivityCacheBustingType Source # 
Eq FloodlightActivityCacheBustingType Source # 
Data FloodlightActivityCacheBustingType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivityCacheBustingType -> c FloodlightActivityCacheBustingType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivityCacheBustingType #

toConstr :: FloodlightActivityCacheBustingType -> Constr #

dataTypeOf :: FloodlightActivityCacheBustingType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivityCacheBustingType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivityCacheBustingType) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivityCacheBustingType -> FloodlightActivityCacheBustingType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityCacheBustingType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityCacheBustingType -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivityCacheBustingType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivityCacheBustingType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivityCacheBustingType -> m FloodlightActivityCacheBustingType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityCacheBustingType -> m FloodlightActivityCacheBustingType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityCacheBustingType -> m FloodlightActivityCacheBustingType #

Ord FloodlightActivityCacheBustingType Source # 
Read FloodlightActivityCacheBustingType Source # 
Show FloodlightActivityCacheBustingType Source # 
Generic FloodlightActivityCacheBustingType Source # 
Hashable FloodlightActivityCacheBustingType Source # 
ToJSON FloodlightActivityCacheBustingType Source # 
FromJSON FloodlightActivityCacheBustingType Source # 
FromHttpApiData FloodlightActivityCacheBustingType Source # 
ToHttpApiData FloodlightActivityCacheBustingType Source # 
type Rep FloodlightActivityCacheBustingType Source # 
type Rep FloodlightActivityCacheBustingType = D1 (MetaData "FloodlightActivityCacheBustingType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "ActiveServerPage" PrefixI False) U1) (C1 (MetaCons "ColdFusion" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Javascript" PrefixI False) U1) ((:+:) (C1 (MetaCons "Jsp" PrefixI False) U1) (C1 (MetaCons "Php" PrefixI False) U1))))

CreativesListResponse

data CreativesListResponse Source #

Creative List Response

See: creativesListResponse smart constructor.

Instances

Eq CreativesListResponse Source # 
Data CreativesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativesListResponse -> c CreativesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativesListResponse #

toConstr :: CreativesListResponse -> Constr #

dataTypeOf :: CreativesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> CreativesListResponse -> CreativesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativesListResponse -> m CreativesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativesListResponse -> m CreativesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativesListResponse -> m CreativesListResponse #

Show CreativesListResponse Source # 
Generic CreativesListResponse Source # 
ToJSON CreativesListResponse Source # 
FromJSON CreativesListResponse Source # 
type Rep CreativesListResponse Source # 
type Rep CreativesListResponse = D1 (MetaData "CreativesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_clrlNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_clrlKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_clrlCreatives") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Creative]))))))

creativesListResponse :: CreativesListResponse Source #

Creates a value of CreativesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

clrlNextPageToken :: Lens' CreativesListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

clrlKind :: Lens' CreativesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#creativesListResponse".

CreativeGroupsListSortOrder

data CreativeGroupsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

CGLSOAscending
ASCENDING
CGLSODescending
DESCENDING

Instances

Enum CreativeGroupsListSortOrder Source # 
Eq CreativeGroupsListSortOrder Source # 
Data CreativeGroupsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeGroupsListSortOrder -> c CreativeGroupsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeGroupsListSortOrder #

toConstr :: CreativeGroupsListSortOrder -> Constr #

dataTypeOf :: CreativeGroupsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeGroupsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeGroupsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> CreativeGroupsListSortOrder -> CreativeGroupsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeGroupsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeGroupsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeGroupsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeGroupsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeGroupsListSortOrder -> m CreativeGroupsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeGroupsListSortOrder -> m CreativeGroupsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeGroupsListSortOrder -> m CreativeGroupsListSortOrder #

Ord CreativeGroupsListSortOrder Source # 
Read CreativeGroupsListSortOrder Source # 
Show CreativeGroupsListSortOrder Source # 
Generic CreativeGroupsListSortOrder Source # 
Hashable CreativeGroupsListSortOrder Source # 
ToJSON CreativeGroupsListSortOrder Source # 
FromJSON CreativeGroupsListSortOrder Source # 
FromHttpApiData CreativeGroupsListSortOrder Source # 
ToHttpApiData CreativeGroupsListSortOrder Source # 
type Rep CreativeGroupsListSortOrder Source # 
type Rep CreativeGroupsListSortOrder = D1 (MetaData "CreativeGroupsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CGLSOAscending" PrefixI False) U1) (C1 (MetaCons "CGLSODescending" PrefixI False) U1))

OrderDocumentType

data OrderDocumentType Source #

Type of this order document

Constructors

PlanningOrderTypeChangeOrder
PLANNING_ORDER_TYPE_CHANGE_ORDER
PlanningOrderTypeInsertionOrder
PLANNING_ORDER_TYPE_INSERTION_ORDER

Instances

Enum OrderDocumentType Source # 
Eq OrderDocumentType Source # 
Data OrderDocumentType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderDocumentType -> c OrderDocumentType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderDocumentType #

toConstr :: OrderDocumentType -> Constr #

dataTypeOf :: OrderDocumentType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderDocumentType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderDocumentType) #

gmapT :: (forall b. Data b => b -> b) -> OrderDocumentType -> OrderDocumentType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderDocumentType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderDocumentType -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderDocumentType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderDocumentType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderDocumentType -> m OrderDocumentType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderDocumentType -> m OrderDocumentType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderDocumentType -> m OrderDocumentType #

Ord OrderDocumentType Source # 
Read OrderDocumentType Source # 
Show OrderDocumentType Source # 
Generic OrderDocumentType Source # 
Hashable OrderDocumentType Source # 
ToJSON OrderDocumentType Source # 
FromJSON OrderDocumentType Source # 
FromHttpApiData OrderDocumentType Source # 
ToHttpApiData OrderDocumentType Source # 
type Rep OrderDocumentType Source # 
type Rep OrderDocumentType = D1 (MetaData "OrderDocumentType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PlanningOrderTypeChangeOrder" PrefixI False) U1) (C1 (MetaCons "PlanningOrderTypeInsertionOrder" PrefixI False) U1))

TagDataFormat

data TagDataFormat Source #

TagData tag format of this tag.

Constructors

PlacementTagClickCommands
PLACEMENT_TAG_CLICK_COMMANDS
PlacementTagIframeIlayer
PLACEMENT_TAG_IFRAME_ILAYER
PlacementTagIframeJavascript
PLACEMENT_TAG_IFRAME_JAVASCRIPT
PlacementTagIframeJavascriptLegacy
PLACEMENT_TAG_IFRAME_JAVASCRIPT_LEGACY
PlacementTagInstreamVideoPrefetch
PLACEMENT_TAG_INSTREAM_VIDEO_PREFETCH
PlacementTagInstreamVideoPrefetchVast3
PLACEMENT_TAG_INSTREAM_VIDEO_PREFETCH_VAST_3
PlacementTagInternalRedirect
PLACEMENT_TAG_INTERNAL_REDIRECT
PlacementTagInterstitialIframeJavascript
PLACEMENT_TAG_INTERSTITIAL_IFRAME_JAVASCRIPT
PlacementTagInterstitialIframeJavascriptLegacy
PLACEMENT_TAG_INTERSTITIAL_IFRAME_JAVASCRIPT_LEGACY
PlacementTagInterstitialInternalRedirect
PLACEMENT_TAG_INTERSTITIAL_INTERNAL_REDIRECT
PlacementTagInterstitialJavascript
PLACEMENT_TAG_INTERSTITIAL_JAVASCRIPT
PlacementTagInterstitialJavascriptLegacy
PLACEMENT_TAG_INTERSTITIAL_JAVASCRIPT_LEGACY
PlacementTagJavascript
PLACEMENT_TAG_JAVASCRIPT
PlacementTagJavascriptLegacy
PLACEMENT_TAG_JAVASCRIPT_LEGACY
PlacementTagStandard
PLACEMENT_TAG_STANDARD
PlacementTagTracking
PLACEMENT_TAG_TRACKING
PlacementTagTrackingIframe
PLACEMENT_TAG_TRACKING_IFRAME
PlacementTagTrackingJavascript
PLACEMENT_TAG_TRACKING_JAVASCRIPT

Instances

Enum TagDataFormat Source # 
Eq TagDataFormat Source # 
Data TagDataFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TagDataFormat -> c TagDataFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TagDataFormat #

toConstr :: TagDataFormat -> Constr #

dataTypeOf :: TagDataFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TagDataFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TagDataFormat) #

gmapT :: (forall b. Data b => b -> b) -> TagDataFormat -> TagDataFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TagDataFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TagDataFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> TagDataFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TagDataFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TagDataFormat -> m TagDataFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TagDataFormat -> m TagDataFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TagDataFormat -> m TagDataFormat #

Ord TagDataFormat Source # 
Read TagDataFormat Source # 
Show TagDataFormat Source # 
Generic TagDataFormat Source # 

Associated Types

type Rep TagDataFormat :: * -> * #

Hashable TagDataFormat Source # 
ToJSON TagDataFormat Source # 
FromJSON TagDataFormat Source # 
FromHttpApiData TagDataFormat Source # 
ToHttpApiData TagDataFormat Source # 
type Rep TagDataFormat Source # 
type Rep TagDataFormat = D1 (MetaData "TagDataFormat" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "PlacementTagClickCommands" PrefixI False) U1) (C1 (MetaCons "PlacementTagIframeIlayer" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PlacementTagIframeJavascript" PrefixI False) U1) (C1 (MetaCons "PlacementTagIframeJavascriptLegacy" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PlacementTagInstreamVideoPrefetch" PrefixI False) U1) (C1 (MetaCons "PlacementTagInstreamVideoPrefetchVast3" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PlacementTagInternalRedirect" PrefixI False) U1) ((:+:) (C1 (MetaCons "PlacementTagInterstitialIframeJavascript" PrefixI False) U1) (C1 (MetaCons "PlacementTagInterstitialIframeJavascriptLegacy" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "PlacementTagInterstitialInternalRedirect" PrefixI False) U1) (C1 (MetaCons "PlacementTagInterstitialJavascript" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PlacementTagInterstitialJavascriptLegacy" PrefixI False) U1) (C1 (MetaCons "PlacementTagJavascript" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PlacementTagJavascriptLegacy" PrefixI False) U1) (C1 (MetaCons "PlacementTagStandard" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PlacementTagTracking" PrefixI False) U1) ((:+:) (C1 (MetaCons "PlacementTagTrackingIframe" PrefixI False) U1) (C1 (MetaCons "PlacementTagTrackingJavascript" PrefixI False) U1))))))

Account

data Account Source #

Contains properties of a DCM account.

See: account smart constructor.

Instances

Eq Account Source # 

Methods

(==) :: Account -> Account -> Bool #

(/=) :: Account -> Account -> Bool #

Data Account Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Account -> c Account #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Account #

toConstr :: Account -> Constr #

dataTypeOf :: Account -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Account) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Account) #

gmapT :: (forall b. Data b => b -> b) -> Account -> Account #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r #

gmapQ :: (forall d. Data d => d -> u) -> Account -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Account -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Account -> m Account #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account #

Show Account Source # 
Generic Account Source # 

Associated Types

type Rep Account :: * -> * #

Methods

from :: Account -> Rep Account x #

to :: Rep Account x -> Account #

ToJSON Account Source # 
FromJSON Account Source # 
type Rep Account Source # 
type Rep Account = D1 (MetaData "Account" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Account'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aaAccountPermissionIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64]))) (S1 (MetaSel (Just Symbol "_aaMaximumImageSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_aaCurrencyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_aaReportsConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportsConfiguration))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aaNielsenOCREnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_aaKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_aaLocale") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_aaActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_aaAvailablePermissionIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64]))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aaTeaserSizeLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_aaComscoreVceEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_aaActiveViewOptOut") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_aaName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aaAccountProFile") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AccountAccountProFile)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aaId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_aaCountryId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_aaActiveAdsLimitTier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AccountActiveAdsLimitTier))) ((:*:) (S1 (MetaSel (Just Symbol "_aaDefaultCreativeSizeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_aaDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))))

aaAccountPermissionIds :: Lens' Account [Int64] Source #

Account permissions assigned to this account.

aaMaximumImageSize :: Lens' Account (Maybe Int64) Source #

Maximum image size allowed for this account.

aaCurrencyId :: Lens' Account (Maybe Int64) Source #

ID of currency associated with this account. This is a required field. Acceptable values are: - "1" for USD - "2" for GBP - "3" for ESP - "4" for SEK - "5" for CAD - "6" for JPY - "7" for DEM - "8" for AUD - "9" for FRF - "10" for ITL - "11" for DKK - "12" for NOK - "13" for FIM - "14" for ZAR - "15" for IEP - "16" for NLG - "17" for EUR - "18" for KRW - "19" for TWD - "20" for SGD - "21" for CNY - "22" for HKD - "23" for NZD - "24" for MYR - "25" for BRL - "26" for PTE - "27" for MXP - "28" for CLP - "29" for TRY - "30" for ARS - "31" for PEN - "32" for ILS - "33" for CHF - "34" for VEF - "35" for COP - "36" for GTQ - "37" for PLN - "39" for INR - "40" for THB - "41" for IDR - "42" for CZK - "43" for RON - "44" for HUF - "45" for RUB - "46" for AED - "47" for BGN - "48" for HRK

aaReportsConfiguration :: Lens' Account (Maybe ReportsConfiguration) Source #

Reporting configuration of this account.

aaNielsenOCREnabled :: Lens' Account (Maybe Bool) Source #

Whether campaigns created in this account will be enabled for Nielsen OCR reach ratings by default.

aaKind :: Lens' Account Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#account".

aaLocale :: Lens' Account (Maybe Text) Source #

Locale of this account. Acceptable values are: - "cs" (Czech) - "de" (German) - "en" (English) - "en-GB" (English United Kingdom) - "es" (Spanish) - "fr" (French) - "it" (Italian) - "ja" (Japanese) - "ko" (Korean) - "pl" (Polish) - "pt-BR" (Portuguese Brazil) - "ru" (Russian) - "sv" (Swedish) - "tr" (Turkish) - "zh-CN" (Chinese Simplified) - "zh-TW" (Chinese Traditional)

aaActive :: Lens' Account (Maybe Bool) Source #

Whether this account is active.

aaAvailablePermissionIds :: Lens' Account [Int64] Source #

User role permissions available to the user roles of this account.

aaTeaserSizeLimit :: Lens' Account (Maybe Int64) Source #

File size limit in kilobytes of Rich Media teaser creatives. Must be between 1 and 10240.

aaComscoreVceEnabled :: Lens' Account (Maybe Bool) Source #

Whether campaigns created in this account will be enabled for comScore vCE by default.

aaActiveViewOptOut :: Lens' Account (Maybe Bool) Source #

Whether to serve creatives with Active View tags. If disabled, viewability data will not be available for any impressions.

aaName :: Lens' Account (Maybe Text) Source #

Name of this account. This is a required field, and must be less than 128 characters long and be globally unique.

aaAccountProFile :: Lens' Account (Maybe AccountAccountProFile) Source #

Profile for this account. This is a read-only field that can be left blank.

aaId :: Lens' Account (Maybe Int64) Source #

ID of this account. This is a read-only, auto-generated field.

aaCountryId :: Lens' Account (Maybe Int64) Source #

ID of the country associated with this account.

aaActiveAdsLimitTier :: Lens' Account (Maybe AccountActiveAdsLimitTier) Source #

Maximum number of active ads allowed for this account.

aaDefaultCreativeSizeId :: Lens' Account (Maybe Int64) Source #

Default placement dimensions for this account.

aaDescription :: Lens' Account (Maybe Text) Source #

Description of this account.

ConversionsBatchInsertRequest

data ConversionsBatchInsertRequest Source #

Insert Conversions Request.

See: conversionsBatchInsertRequest smart constructor.

Instances

Eq ConversionsBatchInsertRequest Source # 
Data ConversionsBatchInsertRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConversionsBatchInsertRequest -> c ConversionsBatchInsertRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConversionsBatchInsertRequest #

toConstr :: ConversionsBatchInsertRequest -> Constr #

dataTypeOf :: ConversionsBatchInsertRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConversionsBatchInsertRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConversionsBatchInsertRequest) #

gmapT :: (forall b. Data b => b -> b) -> ConversionsBatchInsertRequest -> ConversionsBatchInsertRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConversionsBatchInsertRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConversionsBatchInsertRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConversionsBatchInsertRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConversionsBatchInsertRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConversionsBatchInsertRequest -> m ConversionsBatchInsertRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConversionsBatchInsertRequest -> m ConversionsBatchInsertRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConversionsBatchInsertRequest -> m ConversionsBatchInsertRequest #

Show ConversionsBatchInsertRequest Source # 
Generic ConversionsBatchInsertRequest Source # 
ToJSON ConversionsBatchInsertRequest Source # 
FromJSON ConversionsBatchInsertRequest Source # 
type Rep ConversionsBatchInsertRequest Source # 
type Rep ConversionsBatchInsertRequest = D1 (MetaData "ConversionsBatchInsertRequest" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ConversionsBatchInsertRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cbirKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_cbirConversions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Conversion]))) (S1 (MetaSel (Just Symbol "_cbirEncryptionInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EncryptionInfo))))))

conversionsBatchInsertRequest :: ConversionsBatchInsertRequest Source #

Creates a value of ConversionsBatchInsertRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cbirKind :: Lens' ConversionsBatchInsertRequest Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#conversionsBatchInsertRequest".

cbirEncryptionInfo :: Lens' ConversionsBatchInsertRequest (Maybe EncryptionInfo) Source #

Describes how encryptedUserId is encrypted. This is a required field if encryptedUserId is used.

AccountActiveAdSummaryActiveAdsLimitTier

data AccountActiveAdSummaryActiveAdsLimitTier Source #

Maximum number of active ads allowed for the account.

Constructors

ActiveAdsTier100K
ACTIVE_ADS_TIER_100K
ActiveAdsTier200K
ACTIVE_ADS_TIER_200K
ActiveAdsTier300K
ACTIVE_ADS_TIER_300K
ActiveAdsTier40K
ACTIVE_ADS_TIER_40K
ActiveAdsTier75K
ACTIVE_ADS_TIER_75K

Instances

Enum AccountActiveAdSummaryActiveAdsLimitTier Source # 
Eq AccountActiveAdSummaryActiveAdsLimitTier Source # 
Data AccountActiveAdSummaryActiveAdsLimitTier Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountActiveAdSummaryActiveAdsLimitTier -> c AccountActiveAdSummaryActiveAdsLimitTier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountActiveAdSummaryActiveAdsLimitTier #

toConstr :: AccountActiveAdSummaryActiveAdsLimitTier -> Constr #

dataTypeOf :: AccountActiveAdSummaryActiveAdsLimitTier -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountActiveAdSummaryActiveAdsLimitTier) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountActiveAdSummaryActiveAdsLimitTier) #

gmapT :: (forall b. Data b => b -> b) -> AccountActiveAdSummaryActiveAdsLimitTier -> AccountActiveAdSummaryActiveAdsLimitTier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountActiveAdSummaryActiveAdsLimitTier -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountActiveAdSummaryActiveAdsLimitTier -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountActiveAdSummaryActiveAdsLimitTier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountActiveAdSummaryActiveAdsLimitTier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountActiveAdSummaryActiveAdsLimitTier -> m AccountActiveAdSummaryActiveAdsLimitTier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountActiveAdSummaryActiveAdsLimitTier -> m AccountActiveAdSummaryActiveAdsLimitTier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountActiveAdSummaryActiveAdsLimitTier -> m AccountActiveAdSummaryActiveAdsLimitTier #

Ord AccountActiveAdSummaryActiveAdsLimitTier Source # 
Read AccountActiveAdSummaryActiveAdsLimitTier Source # 
Show AccountActiveAdSummaryActiveAdsLimitTier Source # 
Generic AccountActiveAdSummaryActiveAdsLimitTier Source # 
Hashable AccountActiveAdSummaryActiveAdsLimitTier Source # 
ToJSON AccountActiveAdSummaryActiveAdsLimitTier Source # 
FromJSON AccountActiveAdSummaryActiveAdsLimitTier Source # 
FromHttpApiData AccountActiveAdSummaryActiveAdsLimitTier Source # 
ToHttpApiData AccountActiveAdSummaryActiveAdsLimitTier Source # 
type Rep AccountActiveAdSummaryActiveAdsLimitTier Source # 
type Rep AccountActiveAdSummaryActiveAdsLimitTier = D1 (MetaData "AccountActiveAdSummaryActiveAdsLimitTier" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "ActiveAdsTier100K" PrefixI False) U1) (C1 (MetaCons "ActiveAdsTier200K" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ActiveAdsTier300K" PrefixI False) U1) ((:+:) (C1 (MetaCons "ActiveAdsTier40K" PrefixI False) U1) (C1 (MetaCons "ActiveAdsTier75K" PrefixI False) U1))))

CreativeAssetChildAssetType

data CreativeAssetChildAssetType Source #

Rich media child asset type. This is a read-only field. Applicable to the following creative types: all VPAID.

Constructors

ChildAssetTypeData
CHILD_ASSET_TYPE_DATA
ChildAssetTypeFlash
CHILD_ASSET_TYPE_FLASH
ChildAssetTypeImage
CHILD_ASSET_TYPE_IMAGE
ChildAssetTypeVideo
CHILD_ASSET_TYPE_VIDEO

Instances

Enum CreativeAssetChildAssetType Source # 
Eq CreativeAssetChildAssetType Source # 
Data CreativeAssetChildAssetType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetChildAssetType -> c CreativeAssetChildAssetType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetChildAssetType #

toConstr :: CreativeAssetChildAssetType -> Constr #

dataTypeOf :: CreativeAssetChildAssetType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetChildAssetType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetChildAssetType) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetChildAssetType -> CreativeAssetChildAssetType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetChildAssetType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetChildAssetType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetChildAssetType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetChildAssetType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetChildAssetType -> m CreativeAssetChildAssetType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetChildAssetType -> m CreativeAssetChildAssetType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetChildAssetType -> m CreativeAssetChildAssetType #

Ord CreativeAssetChildAssetType Source # 
Read CreativeAssetChildAssetType Source # 
Show CreativeAssetChildAssetType Source # 
Generic CreativeAssetChildAssetType Source # 
Hashable CreativeAssetChildAssetType Source # 
ToJSON CreativeAssetChildAssetType Source # 
FromJSON CreativeAssetChildAssetType Source # 
FromHttpApiData CreativeAssetChildAssetType Source # 
ToHttpApiData CreativeAssetChildAssetType Source # 
type Rep CreativeAssetChildAssetType Source # 
type Rep CreativeAssetChildAssetType = D1 (MetaData "CreativeAssetChildAssetType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "ChildAssetTypeData" PrefixI False) U1) (C1 (MetaCons "ChildAssetTypeFlash" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ChildAssetTypeImage" PrefixI False) U1) (C1 (MetaCons "ChildAssetTypeVideo" PrefixI False) U1)))

PlacementGroupsListPlacementGroupType

data PlacementGroupsListPlacementGroupType Source #

Select only placement groups belonging with this group type. A package is a simple group of placements that acts as a single pricing point for a group of tags. A roadblock is a group of placements that not only acts as a single pricing point but also assumes that all the tags in it will be served at the same time. A roadblock requires one of its assigned placements to be marked as primary for reporting.

Constructors

PlacementPackage
PLACEMENT_PACKAGE
PlacementRoadblock
PLACEMENT_ROADBLOCK

Instances

Enum PlacementGroupsListPlacementGroupType Source # 
Eq PlacementGroupsListPlacementGroupType Source # 
Data PlacementGroupsListPlacementGroupType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementGroupsListPlacementGroupType -> c PlacementGroupsListPlacementGroupType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementGroupsListPlacementGroupType #

toConstr :: PlacementGroupsListPlacementGroupType -> Constr #

dataTypeOf :: PlacementGroupsListPlacementGroupType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementGroupsListPlacementGroupType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementGroupsListPlacementGroupType) #

gmapT :: (forall b. Data b => b -> b) -> PlacementGroupsListPlacementGroupType -> PlacementGroupsListPlacementGroupType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroupsListPlacementGroupType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroupsListPlacementGroupType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementGroupsListPlacementGroupType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementGroupsListPlacementGroupType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementGroupsListPlacementGroupType -> m PlacementGroupsListPlacementGroupType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroupsListPlacementGroupType -> m PlacementGroupsListPlacementGroupType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroupsListPlacementGroupType -> m PlacementGroupsListPlacementGroupType #

Ord PlacementGroupsListPlacementGroupType Source # 
Read PlacementGroupsListPlacementGroupType Source # 
Show PlacementGroupsListPlacementGroupType Source # 
Generic PlacementGroupsListPlacementGroupType Source # 
Hashable PlacementGroupsListPlacementGroupType Source # 
ToJSON PlacementGroupsListPlacementGroupType Source # 
FromJSON PlacementGroupsListPlacementGroupType Source # 
FromHttpApiData PlacementGroupsListPlacementGroupType Source # 
ToHttpApiData PlacementGroupsListPlacementGroupType Source # 
type Rep PlacementGroupsListPlacementGroupType Source # 
type Rep PlacementGroupsListPlacementGroupType = D1 (MetaData "PlacementGroupsListPlacementGroupType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PlacementPackage" PrefixI False) U1) (C1 (MetaCons "PlacementRoadblock" PrefixI False) U1))

AccountUserProFilesListResponse

data AccountUserProFilesListResponse Source #

Account User Profile List Response

See: accountUserProFilesListResponse smart constructor.

Instances

Eq AccountUserProFilesListResponse Source # 
Data AccountUserProFilesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountUserProFilesListResponse -> c AccountUserProFilesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountUserProFilesListResponse #

toConstr :: AccountUserProFilesListResponse -> Constr #

dataTypeOf :: AccountUserProFilesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountUserProFilesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountUserProFilesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> AccountUserProFilesListResponse -> AccountUserProFilesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountUserProFilesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountUserProFilesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountUserProFilesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountUserProFilesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountUserProFilesListResponse -> m AccountUserProFilesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountUserProFilesListResponse -> m AccountUserProFilesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountUserProFilesListResponse -> m AccountUserProFilesListResponse #

Show AccountUserProFilesListResponse Source # 
Generic AccountUserProFilesListResponse Source # 
ToJSON AccountUserProFilesListResponse Source # 
FromJSON AccountUserProFilesListResponse Source # 
type Rep AccountUserProFilesListResponse Source # 
type Rep AccountUserProFilesListResponse = D1 (MetaData "AccountUserProFilesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AccountUserProFilesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_aupflrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_aupflrAccountUserProFiles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AccountUserProFile]))) (S1 (MetaSel (Just Symbol "_aupflrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

accountUserProFilesListResponse :: AccountUserProFilesListResponse Source #

Creates a value of AccountUserProFilesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

aupflrNextPageToken :: Lens' AccountUserProFilesListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

aupflrKind :: Lens' AccountUserProFilesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#accountUserProfilesListResponse".

ContentCategory

data ContentCategory Source #

Organizes placements according to the contents of their associated webpages.

See: contentCategory smart constructor.

Instances

Eq ContentCategory Source # 
Data ContentCategory Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ContentCategory -> c ContentCategory #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ContentCategory #

toConstr :: ContentCategory -> Constr #

dataTypeOf :: ContentCategory -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ContentCategory) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ContentCategory) #

gmapT :: (forall b. Data b => b -> b) -> ContentCategory -> ContentCategory #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ContentCategory -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ContentCategory -> r #

gmapQ :: (forall d. Data d => d -> u) -> ContentCategory -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ContentCategory -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ContentCategory -> m ContentCategory #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ContentCategory -> m ContentCategory #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ContentCategory -> m ContentCategory #

Show ContentCategory Source # 
Generic ContentCategory Source # 
ToJSON ContentCategory Source # 
FromJSON ContentCategory Source # 
type Rep ContentCategory Source # 
type Rep ContentCategory = D1 (MetaData "ContentCategory" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ContentCategory'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_conKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_conAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_conName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_conId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

contentCategory :: ContentCategory Source #

Creates a value of ContentCategory with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

conKind :: Lens' ContentCategory Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#contentCategory".

conAccountId :: Lens' ContentCategory (Maybe Int64) Source #

Account ID of this content category. This is a read-only field that can be left blank.

conName :: Lens' ContentCategory (Maybe Text) Source #

Name of this content category. This is a required field and must be less than 256 characters long and unique among content categories of the same account.

conId :: Lens' ContentCategory (Maybe Int64) Source #

ID of this content category. This is a read-only, auto-generated field.

ObjectFilterStatus

data ObjectFilterStatus Source #

Status of the filter. NONE means the user has access to none of the objects. ALL means the user has access to all objects. ASSIGNED means the user has access to the objects with IDs in the objectIds list.

Constructors

OFSAll
ALL
OFSAssigned
ASSIGNED
OFSNone
NONE

Instances

Enum ObjectFilterStatus Source # 
Eq ObjectFilterStatus Source # 
Data ObjectFilterStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjectFilterStatus -> c ObjectFilterStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjectFilterStatus #

toConstr :: ObjectFilterStatus -> Constr #

dataTypeOf :: ObjectFilterStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ObjectFilterStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjectFilterStatus) #

gmapT :: (forall b. Data b => b -> b) -> ObjectFilterStatus -> ObjectFilterStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjectFilterStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjectFilterStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> ObjectFilterStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjectFilterStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjectFilterStatus -> m ObjectFilterStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectFilterStatus -> m ObjectFilterStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectFilterStatus -> m ObjectFilterStatus #

Ord ObjectFilterStatus Source # 
Read ObjectFilterStatus Source # 
Show ObjectFilterStatus Source # 
Generic ObjectFilterStatus Source # 
Hashable ObjectFilterStatus Source # 
ToJSON ObjectFilterStatus Source # 
FromJSON ObjectFilterStatus Source # 
FromHttpApiData ObjectFilterStatus Source # 
ToHttpApiData ObjectFilterStatus Source # 
type Rep ObjectFilterStatus Source # 
type Rep ObjectFilterStatus = D1 (MetaData "ObjectFilterStatus" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "OFSAll" PrefixI False) U1) ((:+:) (C1 (MetaCons "OFSAssigned" PrefixI False) U1) (C1 (MetaCons "OFSNone" PrefixI False) U1)))

ReportCompatibleFields

data ReportCompatibleFields Source #

Represents fields that are compatible to be selected for a report of type "STANDARD".

See: reportCompatibleFields smart constructor.

Instances

Eq ReportCompatibleFields Source # 
Data ReportCompatibleFields Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportCompatibleFields -> c ReportCompatibleFields #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportCompatibleFields #

toConstr :: ReportCompatibleFields -> Constr #

dataTypeOf :: ReportCompatibleFields -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportCompatibleFields) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportCompatibleFields) #

gmapT :: (forall b. Data b => b -> b) -> ReportCompatibleFields -> ReportCompatibleFields #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportCompatibleFields -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportCompatibleFields -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportCompatibleFields -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportCompatibleFields -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportCompatibleFields -> m ReportCompatibleFields #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportCompatibleFields -> m ReportCompatibleFields #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportCompatibleFields -> m ReportCompatibleFields #

Show ReportCompatibleFields Source # 
Generic ReportCompatibleFields Source # 
ToJSON ReportCompatibleFields Source # 
FromJSON ReportCompatibleFields Source # 
type Rep ReportCompatibleFields Source # 
type Rep ReportCompatibleFields = D1 (MetaData "ReportCompatibleFields" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ReportCompatibleFields'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcfMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Metric]))) (S1 (MetaSel (Just Symbol "_rcfKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rcfDimensionFilters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension]))) ((:*:) (S1 (MetaSel (Just Symbol "_rcfPivotedActivityMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Metric]))) (S1 (MetaSel (Just Symbol "_rcfDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension])))))))

reportCompatibleFields :: ReportCompatibleFields Source #

Creates a value of ReportCompatibleFields with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rcfMetrics :: Lens' ReportCompatibleFields [Metric] Source #

Metrics which are compatible to be selected in the "metricNames" section of the report.

rcfKind :: Lens' ReportCompatibleFields Text Source #

The kind of resource this is, in this case dfareporting#reportCompatibleFields.

rcfDimensionFilters :: Lens' ReportCompatibleFields [Dimension] Source #

Dimensions which are compatible to be selected in the "dimensionFilters" section of the report.

rcfPivotedActivityMetrics :: Lens' ReportCompatibleFields [Metric] Source #

Metrics which are compatible to be selected as activity metrics to pivot on in the "activities" section of the report.

rcfDimensions :: Lens' ReportCompatibleFields [Dimension] Source #

Dimensions which are compatible to be selected in the "dimensions" section of the report.

CampaignCreativeAssociationsListSortOrder

data CampaignCreativeAssociationsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

CCALSOAscending
ASCENDING
CCALSODescending
DESCENDING

Instances

Enum CampaignCreativeAssociationsListSortOrder Source # 
Eq CampaignCreativeAssociationsListSortOrder Source # 
Data CampaignCreativeAssociationsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CampaignCreativeAssociationsListSortOrder -> c CampaignCreativeAssociationsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CampaignCreativeAssociationsListSortOrder #

toConstr :: CampaignCreativeAssociationsListSortOrder -> Constr #

dataTypeOf :: CampaignCreativeAssociationsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CampaignCreativeAssociationsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CampaignCreativeAssociationsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> CampaignCreativeAssociationsListSortOrder -> CampaignCreativeAssociationsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CampaignCreativeAssociationsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CampaignCreativeAssociationsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> CampaignCreativeAssociationsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CampaignCreativeAssociationsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CampaignCreativeAssociationsListSortOrder -> m CampaignCreativeAssociationsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignCreativeAssociationsListSortOrder -> m CampaignCreativeAssociationsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignCreativeAssociationsListSortOrder -> m CampaignCreativeAssociationsListSortOrder #

Ord CampaignCreativeAssociationsListSortOrder Source # 
Read CampaignCreativeAssociationsListSortOrder Source # 
Show CampaignCreativeAssociationsListSortOrder Source # 
Generic CampaignCreativeAssociationsListSortOrder Source # 
Hashable CampaignCreativeAssociationsListSortOrder Source # 
ToJSON CampaignCreativeAssociationsListSortOrder Source # 
FromJSON CampaignCreativeAssociationsListSortOrder Source # 
FromHttpApiData CampaignCreativeAssociationsListSortOrder Source # 
ToHttpApiData CampaignCreativeAssociationsListSortOrder Source # 
type Rep CampaignCreativeAssociationsListSortOrder Source # 
type Rep CampaignCreativeAssociationsListSortOrder = D1 (MetaData "CampaignCreativeAssociationsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CCALSOAscending" PrefixI False) U1) (C1 (MetaCons "CCALSODescending" PrefixI False) U1))

DeliverySchedule

data DeliverySchedule Source #

Delivery Schedule.

See: deliverySchedule smart constructor.

Instances

Eq DeliverySchedule Source # 
Data DeliverySchedule Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeliverySchedule -> c DeliverySchedule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeliverySchedule #

toConstr :: DeliverySchedule -> Constr #

dataTypeOf :: DeliverySchedule -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeliverySchedule) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeliverySchedule) #

gmapT :: (forall b. Data b => b -> b) -> DeliverySchedule -> DeliverySchedule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeliverySchedule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeliverySchedule -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeliverySchedule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeliverySchedule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeliverySchedule -> m DeliverySchedule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeliverySchedule -> m DeliverySchedule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeliverySchedule -> m DeliverySchedule #

Show DeliverySchedule Source # 
Generic DeliverySchedule Source # 
ToJSON DeliverySchedule Source # 
FromJSON DeliverySchedule Source # 
type Rep DeliverySchedule Source # 
type Rep DeliverySchedule = D1 (MetaData "DeliverySchedule" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DeliverySchedule'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dsHardCutoff") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_dsPriority") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeliverySchedulePriority)))) ((:*:) (S1 (MetaSel (Just Symbol "_dsImpressionRatio") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_dsFrequencyCap") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FrequencyCap))))))

deliverySchedule :: DeliverySchedule Source #

Creates a value of DeliverySchedule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dsHardCutoff :: Lens' DeliverySchedule (Maybe Bool) Source #

Whether or not hard cutoff is enabled. If true, the ad will not serve after the end date and time. Otherwise the ad will continue to be served until it has reached its delivery goals.

dsPriority :: Lens' DeliverySchedule (Maybe DeliverySchedulePriority) Source #

Serving priority of an ad, with respect to other ads. The lower the priority number, the greater the priority with which it is served.

dsImpressionRatio :: Lens' DeliverySchedule (Maybe Int64) Source #

Impression ratio for this ad. This ratio determines how often each ad is served relative to the others. For example, if ad A has an impression ratio of 1 and ad B has an impression ratio of 3, then DCM will serve ad B three times as often as ad A. Must be between 1 and 10.

dsFrequencyCap :: Lens' DeliverySchedule (Maybe FrequencyCap) Source #

Limit on the number of times an individual user can be served the ad within a specified period of time.

RemarketingList

data RemarketingList Source #

Contains properties of a remarketing list. Remarketing enables you to create lists of users who have performed specific actions on a site, then target ads to members of those lists. This resource can be used to manage remarketing lists that are owned by your advertisers. To see all remarketing lists that are visible to your advertisers, including those that are shared to your advertiser or account, use the TargetableRemarketingLists resource.

See: remarketingList smart constructor.

Instances

Eq RemarketingList Source # 
Data RemarketingList Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RemarketingList -> c RemarketingList #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RemarketingList #

toConstr :: RemarketingList -> Constr #

dataTypeOf :: RemarketingList -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RemarketingList) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RemarketingList) #

gmapT :: (forall b. Data b => b -> b) -> RemarketingList -> RemarketingList #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RemarketingList -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RemarketingList -> r #

gmapQ :: (forall d. Data d => d -> u) -> RemarketingList -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RemarketingList -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RemarketingList -> m RemarketingList #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RemarketingList -> m RemarketingList #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RemarketingList -> m RemarketingList #

Show RemarketingList Source # 
Generic RemarketingList Source # 
ToJSON RemarketingList Source # 
FromJSON RemarketingList Source # 
type Rep RemarketingList Source # 
type Rep RemarketingList = D1 (MetaData "RemarketingList" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "RemarketingList'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rlListSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_rlListPopulationRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ListPopulationRule))) (S1 (MetaSel (Just Symbol "_rlLifeSpan") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) (S1 (MetaSel (Just Symbol "_rlKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_rlAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_rlAdvertiserIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rlActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_rlAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_rlName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rlListSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RemarketingListListSource))) (S1 (MetaSel (Just Symbol "_rlId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_rlSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_rlDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

remarketingList :: RemarketingList Source #

Creates a value of RemarketingList with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rlListSize :: Lens' RemarketingList (Maybe Int64) Source #

Number of users currently in the list. This is a read-only field.

rlListPopulationRule :: Lens' RemarketingList (Maybe ListPopulationRule) Source #

Rule used to populate the remarketing list with users.

rlLifeSpan :: Lens' RemarketingList (Maybe Int64) Source #

Number of days that a user should remain in the remarketing list without an impression.

rlKind :: Lens' RemarketingList Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#remarketingList".

rlAdvertiserId :: Lens' RemarketingList (Maybe Int64) Source #

Dimension value for the advertiser ID that owns this remarketing list. This is a required field.

rlAdvertiserIdDimensionValue :: Lens' RemarketingList (Maybe DimensionValue) Source #

Dimension value for the ID of the advertiser. This is a read-only, auto-generated field.

rlActive :: Lens' RemarketingList (Maybe Bool) Source #

Whether this remarketing list is active.

rlAccountId :: Lens' RemarketingList (Maybe Int64) Source #

Account ID of this remarketing list. This is a read-only, auto-generated field that is only returned in GET requests.

rlName :: Lens' RemarketingList (Maybe Text) Source #

Name of the remarketing list. This is a required field. Must be no greater than 128 characters long.

rlListSource :: Lens' RemarketingList (Maybe RemarketingListListSource) Source #

Product from which this remarketing list was originated.

rlId :: Lens' RemarketingList (Maybe Int64) Source #

Remarketing list ID. This is a read-only, auto-generated field.

rlSubAccountId :: Lens' RemarketingList (Maybe Int64) Source #

Subaccount ID of this remarketing list. This is a read-only, auto-generated field that is only returned in GET requests.

rlDescription :: Lens' RemarketingList (Maybe Text) Source #

Remarketing list description.

FloodlightActivitiesListSortField

data FloodlightActivitiesListSortField Source #

Field by which to sort the list.

Constructors

FALSFID
ID
FALSFName
NAME

Instances

Enum FloodlightActivitiesListSortField Source # 
Eq FloodlightActivitiesListSortField Source # 
Data FloodlightActivitiesListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivitiesListSortField -> c FloodlightActivitiesListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivitiesListSortField #

toConstr :: FloodlightActivitiesListSortField -> Constr #

dataTypeOf :: FloodlightActivitiesListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivitiesListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivitiesListSortField) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivitiesListSortField -> FloodlightActivitiesListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivitiesListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivitiesListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivitiesListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivitiesListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivitiesListSortField -> m FloodlightActivitiesListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivitiesListSortField -> m FloodlightActivitiesListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivitiesListSortField -> m FloodlightActivitiesListSortField #

Ord FloodlightActivitiesListSortField Source # 
Read FloodlightActivitiesListSortField Source # 
Show FloodlightActivitiesListSortField Source # 
Generic FloodlightActivitiesListSortField Source # 
Hashable FloodlightActivitiesListSortField Source # 
ToJSON FloodlightActivitiesListSortField Source # 
FromJSON FloodlightActivitiesListSortField Source # 
FromHttpApiData FloodlightActivitiesListSortField Source # 
ToHttpApiData FloodlightActivitiesListSortField Source # 
type Rep FloodlightActivitiesListSortField Source # 
type Rep FloodlightActivitiesListSortField = D1 (MetaData "FloodlightActivitiesListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "FALSFID" PrefixI False) U1) (C1 (MetaCons "FALSFName" PrefixI False) U1))

DynamicTargetingKeysListResponse

data DynamicTargetingKeysListResponse Source #

Dynamic Targeting Key List Response

See: dynamicTargetingKeysListResponse smart constructor.

Instances

Eq DynamicTargetingKeysListResponse Source # 
Data DynamicTargetingKeysListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DynamicTargetingKeysListResponse -> c DynamicTargetingKeysListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DynamicTargetingKeysListResponse #

toConstr :: DynamicTargetingKeysListResponse -> Constr #

dataTypeOf :: DynamicTargetingKeysListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DynamicTargetingKeysListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DynamicTargetingKeysListResponse) #

gmapT :: (forall b. Data b => b -> b) -> DynamicTargetingKeysListResponse -> DynamicTargetingKeysListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DynamicTargetingKeysListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DynamicTargetingKeysListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> DynamicTargetingKeysListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DynamicTargetingKeysListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DynamicTargetingKeysListResponse -> m DynamicTargetingKeysListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DynamicTargetingKeysListResponse -> m DynamicTargetingKeysListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DynamicTargetingKeysListResponse -> m DynamicTargetingKeysListResponse #

Show DynamicTargetingKeysListResponse Source # 
Generic DynamicTargetingKeysListResponse Source # 
ToJSON DynamicTargetingKeysListResponse Source # 
FromJSON DynamicTargetingKeysListResponse Source # 
type Rep DynamicTargetingKeysListResponse Source # 
type Rep DynamicTargetingKeysListResponse = D1 (MetaData "DynamicTargetingKeysListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DynamicTargetingKeysListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dtklrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_dtklrDynamicTargetingKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DynamicTargetingKey])))))

dynamicTargetingKeysListResponse :: DynamicTargetingKeysListResponse Source #

Creates a value of DynamicTargetingKeysListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dtklrKind :: Lens' DynamicTargetingKeysListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#dynamicTargetingKeysListResponse".

DimensionValueList

data DimensionValueList Source #

Represents the list of DimensionValue resources.

See: dimensionValueList smart constructor.

Instances

Eq DimensionValueList Source # 
Data DimensionValueList Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DimensionValueList -> c DimensionValueList #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DimensionValueList #

toConstr :: DimensionValueList -> Constr #

dataTypeOf :: DimensionValueList -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DimensionValueList) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DimensionValueList) #

gmapT :: (forall b. Data b => b -> b) -> DimensionValueList -> DimensionValueList #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DimensionValueList -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DimensionValueList -> r #

gmapQ :: (forall d. Data d => d -> u) -> DimensionValueList -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DimensionValueList -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DimensionValueList -> m DimensionValueList #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionValueList -> m DimensionValueList #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionValueList -> m DimensionValueList #

Show DimensionValueList Source # 
Generic DimensionValueList Source # 
ToJSON DimensionValueList Source # 
FromJSON DimensionValueList Source # 
type Rep DimensionValueList Source # 
type Rep DimensionValueList = D1 (MetaData "DimensionValueList" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DimensionValueList'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dvlEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dvlNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_dvlKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_dvlItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DimensionValue]))))))

dimensionValueList :: DimensionValueList Source #

Creates a value of DimensionValueList with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dvlEtag :: Lens' DimensionValueList (Maybe Text) Source #

The eTag of this response for caching purposes.

dvlNextPageToken :: Lens' DimensionValueList (Maybe Text) Source #

Continuation token used to page through dimension values. To retrieve the next page of results, set the next request's "pageToken" to the value of this field. The page token is only valid for a limited amount of time and should not be persisted.

dvlKind :: Lens' DimensionValueList Text Source #

The kind of list this is, in this case dfareporting#dimensionValueList.

dvlItems :: Lens' DimensionValueList [DimensionValue] Source #

The dimension values returned in this response.

FloodlightReportCompatibleFields

data FloodlightReportCompatibleFields Source #

Represents fields that are compatible to be selected for a report of type "FlOODLIGHT".

See: floodlightReportCompatibleFields smart constructor.

Instances

Eq FloodlightReportCompatibleFields Source # 
Data FloodlightReportCompatibleFields Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightReportCompatibleFields -> c FloodlightReportCompatibleFields #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightReportCompatibleFields #

toConstr :: FloodlightReportCompatibleFields -> Constr #

dataTypeOf :: FloodlightReportCompatibleFields -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightReportCompatibleFields) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightReportCompatibleFields) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightReportCompatibleFields -> FloodlightReportCompatibleFields #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightReportCompatibleFields -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightReportCompatibleFields -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightReportCompatibleFields -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightReportCompatibleFields -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightReportCompatibleFields -> m FloodlightReportCompatibleFields #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightReportCompatibleFields -> m FloodlightReportCompatibleFields #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightReportCompatibleFields -> m FloodlightReportCompatibleFields #

Show FloodlightReportCompatibleFields Source # 
Generic FloodlightReportCompatibleFields Source # 
ToJSON FloodlightReportCompatibleFields Source # 
FromJSON FloodlightReportCompatibleFields Source # 
type Rep FloodlightReportCompatibleFields Source # 
type Rep FloodlightReportCompatibleFields = D1 (MetaData "FloodlightReportCompatibleFields" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FloodlightReportCompatibleFields'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_frcfMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Metric]))) (S1 (MetaSel (Just Symbol "_frcfKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_frcfDimensionFilters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension]))) (S1 (MetaSel (Just Symbol "_frcfDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension]))))))

floodlightReportCompatibleFields :: FloodlightReportCompatibleFields Source #

Creates a value of FloodlightReportCompatibleFields with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

frcfMetrics :: Lens' FloodlightReportCompatibleFields [Metric] Source #

Metrics which are compatible to be selected in the "metricNames" section of the report.

frcfKind :: Lens' FloodlightReportCompatibleFields Text Source #

The kind of resource this is, in this case dfareporting#floodlightReportCompatibleFields.

frcfDimensionFilters :: Lens' FloodlightReportCompatibleFields [Dimension] Source #

Dimensions which are compatible to be selected in the "dimensionFilters" section of the report.

frcfDimensions :: Lens' FloodlightReportCompatibleFields [Dimension] Source #

Dimensions which are compatible to be selected in the "dimensions" section of the report.

UserRolePermissionGroup

data UserRolePermissionGroup Source #

Represents a grouping of related user role permissions.

See: userRolePermissionGroup smart constructor.

Instances

Eq UserRolePermissionGroup Source # 
Data UserRolePermissionGroup Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserRolePermissionGroup -> c UserRolePermissionGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserRolePermissionGroup #

toConstr :: UserRolePermissionGroup -> Constr #

dataTypeOf :: UserRolePermissionGroup -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserRolePermissionGroup) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserRolePermissionGroup) #

gmapT :: (forall b. Data b => b -> b) -> UserRolePermissionGroup -> UserRolePermissionGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserRolePermissionGroup -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserRolePermissionGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserRolePermissionGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserRolePermissionGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserRolePermissionGroup -> m UserRolePermissionGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRolePermissionGroup -> m UserRolePermissionGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRolePermissionGroup -> m UserRolePermissionGroup #

Show UserRolePermissionGroup Source # 
Generic UserRolePermissionGroup Source # 
ToJSON UserRolePermissionGroup Source # 
FromJSON UserRolePermissionGroup Source # 
type Rep UserRolePermissionGroup Source # 
type Rep UserRolePermissionGroup = D1 (MetaData "UserRolePermissionGroup" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "UserRolePermissionGroup'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_urpgKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_urpgName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_urpgId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

userRolePermissionGroup :: UserRolePermissionGroup Source #

Creates a value of UserRolePermissionGroup with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

urpgKind :: Lens' UserRolePermissionGroup Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#userRolePermissionGroup".

urpgName :: Lens' UserRolePermissionGroup (Maybe Text) Source #

Name of this user role permission group.

urpgId :: Lens' UserRolePermissionGroup (Maybe Int64) Source #

ID of this user role permission.

CreativesListTypes

data CreativesListTypes Source #

Select only creatives with these creative types.

Constructors

CLTBrandSafeDefaultInstreamVideo
BRAND_SAFE_DEFAULT_INSTREAM_VIDEO
CLTCustomDisplay
CUSTOM_DISPLAY
CLTCustomDisplayInterstitial
CUSTOM_DISPLAY_INTERSTITIAL
CLTDisplay
DISPLAY
CLTDisplayImageGallery
DISPLAY_IMAGE_GALLERY
CLTDisplayRedirect
DISPLAY_REDIRECT
CLTFlashInpage
FLASH_INPAGE
CLTHTML5Banner
HTML5_BANNER
CLTImage
IMAGE
CLTInstreamVideo
INSTREAM_VIDEO
CLTInstreamVideoRedirect
INSTREAM_VIDEO_REDIRECT
CLTInternalRedirect
INTERNAL_REDIRECT
CLTInterstitialInternalRedirect
INTERSTITIAL_INTERNAL_REDIRECT
CLTRichMediaDisplayBanner
RICH_MEDIA_DISPLAY_BANNER
CLTRichMediaDisplayExpanding
RICH_MEDIA_DISPLAY_EXPANDING
CLTRichMediaDisplayInterstitial
RICH_MEDIA_DISPLAY_INTERSTITIAL
CLTRichMediaDisplayMultiFloatingInterstitial
RICH_MEDIA_DISPLAY_MULTI_FLOATING_INTERSTITIAL
CLTRichMediaImExpand
RICH_MEDIA_IM_EXPAND
CLTRichMediaInpageFloating
RICH_MEDIA_INPAGE_FLOATING
CLTRichMediaMobileInApp
RICH_MEDIA_MOBILE_IN_APP
CLTRichMediaPeelDown
RICH_MEDIA_PEEL_DOWN
CLTTrackingText
TRACKING_TEXT
CLTVpaidLinearVideo
VPAID_LINEAR_VIDEO
CLTVpaidNonLinearVideo
VPAID_NON_LINEAR_VIDEO

Instances

Enum CreativesListTypes Source # 
Eq CreativesListTypes Source # 
Data CreativesListTypes Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativesListTypes -> c CreativesListTypes #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativesListTypes #

toConstr :: CreativesListTypes -> Constr #

dataTypeOf :: CreativesListTypes -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativesListTypes) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativesListTypes) #

gmapT :: (forall b. Data b => b -> b) -> CreativesListTypes -> CreativesListTypes #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativesListTypes -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativesListTypes -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativesListTypes -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativesListTypes -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativesListTypes -> m CreativesListTypes #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativesListTypes -> m CreativesListTypes #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativesListTypes -> m CreativesListTypes #

Ord CreativesListTypes Source # 
Read CreativesListTypes Source # 
Show CreativesListTypes Source # 
Generic CreativesListTypes Source # 
Hashable CreativesListTypes Source # 
ToJSON CreativesListTypes Source # 
FromJSON CreativesListTypes Source # 
FromHttpApiData CreativesListTypes Source # 
ToHttpApiData CreativesListTypes Source # 
type Rep CreativesListTypes Source # 
type Rep CreativesListTypes = D1 (MetaData "CreativesListTypes" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CLTBrandSafeDefaultInstreamVideo" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLTCustomDisplay" PrefixI False) U1) (C1 (MetaCons "CLTCustomDisplayInterstitial" PrefixI False) U1))) ((:+:) (C1 (MetaCons "CLTDisplay" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLTDisplayImageGallery" PrefixI False) U1) (C1 (MetaCons "CLTDisplayRedirect" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "CLTFlashInpage" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLTHTML5Banner" PrefixI False) U1) (C1 (MetaCons "CLTImage" PrefixI False) U1))) ((:+:) (C1 (MetaCons "CLTInstreamVideo" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLTInstreamVideoRedirect" PrefixI False) U1) (C1 (MetaCons "CLTInternalRedirect" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CLTInterstitialInternalRedirect" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLTRichMediaDisplayBanner" PrefixI False) U1) (C1 (MetaCons "CLTRichMediaDisplayExpanding" PrefixI False) U1))) ((:+:) (C1 (MetaCons "CLTRichMediaDisplayInterstitial" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLTRichMediaDisplayMultiFloatingInterstitial" PrefixI False) U1) (C1 (MetaCons "CLTRichMediaImExpand" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "CLTRichMediaInpageFloating" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLTRichMediaMobileInApp" PrefixI False) U1) (C1 (MetaCons "CLTRichMediaPeelDown" PrefixI False) U1))) ((:+:) (C1 (MetaCons "CLTTrackingText" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLTVpaidLinearVideo" PrefixI False) U1) (C1 (MetaCons "CLTVpaidNonLinearVideo" PrefixI False) U1))))))

DirectorySiteInpageTagFormatsItem

data DirectorySiteInpageTagFormatsItem Source #

Constructors

IframeJavascriptInpage
IFRAME_JAVASCRIPT_INPAGE
InternalRedirectInpage
INTERNAL_REDIRECT_INPAGE
JavascriptInpage
JAVASCRIPT_INPAGE
Standard
STANDARD

Instances

Enum DirectorySiteInpageTagFormatsItem Source # 
Eq DirectorySiteInpageTagFormatsItem Source # 
Data DirectorySiteInpageTagFormatsItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectorySiteInpageTagFormatsItem -> c DirectorySiteInpageTagFormatsItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectorySiteInpageTagFormatsItem #

toConstr :: DirectorySiteInpageTagFormatsItem -> Constr #

dataTypeOf :: DirectorySiteInpageTagFormatsItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectorySiteInpageTagFormatsItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectorySiteInpageTagFormatsItem) #

gmapT :: (forall b. Data b => b -> b) -> DirectorySiteInpageTagFormatsItem -> DirectorySiteInpageTagFormatsItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteInpageTagFormatsItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteInpageTagFormatsItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectorySiteInpageTagFormatsItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectorySiteInpageTagFormatsItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectorySiteInpageTagFormatsItem -> m DirectorySiteInpageTagFormatsItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteInpageTagFormatsItem -> m DirectorySiteInpageTagFormatsItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteInpageTagFormatsItem -> m DirectorySiteInpageTagFormatsItem #

Ord DirectorySiteInpageTagFormatsItem Source # 
Read DirectorySiteInpageTagFormatsItem Source # 
Show DirectorySiteInpageTagFormatsItem Source # 
Generic DirectorySiteInpageTagFormatsItem Source # 
Hashable DirectorySiteInpageTagFormatsItem Source # 
ToJSON DirectorySiteInpageTagFormatsItem Source # 
FromJSON DirectorySiteInpageTagFormatsItem Source # 
FromHttpApiData DirectorySiteInpageTagFormatsItem Source # 
ToHttpApiData DirectorySiteInpageTagFormatsItem Source # 
type Rep DirectorySiteInpageTagFormatsItem Source # 
type Rep DirectorySiteInpageTagFormatsItem = D1 (MetaData "DirectorySiteInpageTagFormatsItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "IframeJavascriptInpage" PrefixI False) U1) (C1 (MetaCons "InternalRedirectInpage" PrefixI False) U1)) ((:+:) (C1 (MetaCons "JavascriptInpage" PrefixI False) U1) (C1 (MetaCons "Standard" PrefixI False) U1)))

TagSetting

data TagSetting Source #

Tag Settings

See: tagSetting smart constructor.

Instances

Eq TagSetting Source # 
Data TagSetting Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TagSetting -> c TagSetting #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TagSetting #

toConstr :: TagSetting -> Constr #

dataTypeOf :: TagSetting -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TagSetting) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TagSetting) #

gmapT :: (forall b. Data b => b -> b) -> TagSetting -> TagSetting #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TagSetting -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TagSetting -> r #

gmapQ :: (forall d. Data d => d -> u) -> TagSetting -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TagSetting -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TagSetting -> m TagSetting #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TagSetting -> m TagSetting #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TagSetting -> m TagSetting #

Show TagSetting Source # 
Generic TagSetting Source # 

Associated Types

type Rep TagSetting :: * -> * #

ToJSON TagSetting Source # 
FromJSON TagSetting Source # 
type Rep TagSetting Source # 
type Rep TagSetting = D1 (MetaData "TagSetting" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "TagSetting'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_tsKeywordOption") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TagSettingKeywordOption))) (S1 (MetaSel (Just Symbol "_tsIncludeClickThroughURLs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_tsIncludeClickTracking") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_tsAdditionalKeyValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

tagSetting :: TagSetting Source #

Creates a value of TagSetting with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tsKeywordOption :: Lens' TagSetting (Maybe TagSettingKeywordOption) Source #

Option specifying how keywords are embedded in ad tags. This setting can be used to specify whether keyword placeholders are inserted in placement tags for this site. Publishers can then add keywords to those placeholders.

tsIncludeClickThroughURLs :: Lens' TagSetting (Maybe Bool) Source #

Whether static landing page URLs should be included in the tags. This setting applies only to placements.

tsIncludeClickTracking :: Lens' TagSetting (Maybe Bool) Source #

Whether click-tracking string should be included in the tags.

tsAdditionalKeyValues :: Lens' TagSetting (Maybe Text) Source #

Additional key-values to be included in tags. Each key-value pair must be of the form key=value, and pairs must be separated by a semicolon (;). Keys and values must not contain commas. For example, id=2;color=red is a valid value for this field.

CreativeAssetWindowMode

data CreativeAssetWindowMode Source #

Window mode options for flash assets. Applicable to the following creative types: FLASH_INPAGE, RICH_MEDIA_DISPLAY_EXPANDING, RICH_MEDIA_IM_EXPAND, RICH_MEDIA_DISPLAY_BANNER, and RICH_MEDIA_INPAGE_FLOATING.

Constructors

Opaque
OPAQUE
Transparent
TRANSPARENT
Window
WINDOW

Instances

Enum CreativeAssetWindowMode Source # 
Eq CreativeAssetWindowMode Source # 
Data CreativeAssetWindowMode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetWindowMode -> c CreativeAssetWindowMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetWindowMode #

toConstr :: CreativeAssetWindowMode -> Constr #

dataTypeOf :: CreativeAssetWindowMode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetWindowMode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetWindowMode) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetWindowMode -> CreativeAssetWindowMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetWindowMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetWindowMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetWindowMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetWindowMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetWindowMode -> m CreativeAssetWindowMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetWindowMode -> m CreativeAssetWindowMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetWindowMode -> m CreativeAssetWindowMode #

Ord CreativeAssetWindowMode Source # 
Read CreativeAssetWindowMode Source # 
Show CreativeAssetWindowMode Source # 
Generic CreativeAssetWindowMode Source # 
Hashable CreativeAssetWindowMode Source # 
ToJSON CreativeAssetWindowMode Source # 
FromJSON CreativeAssetWindowMode Source # 
FromHttpApiData CreativeAssetWindowMode Source # 
ToHttpApiData CreativeAssetWindowMode Source # 
type Rep CreativeAssetWindowMode Source # 
type Rep CreativeAssetWindowMode = D1 (MetaData "CreativeAssetWindowMode" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Opaque" PrefixI False) U1) ((:+:) (C1 (MetaCons "Transparent" PrefixI False) U1) (C1 (MetaCons "Window" PrefixI False) U1)))

CreativeAssetAlignment

data CreativeAssetAlignment Source #

Possible alignments for an asset. This is a read-only field. Applicable to the following creative types: RICH_MEDIA_DISPLAY_MULTI_FLOATING_INTERSTITIAL.

Constructors

AlignmentBottom
ALIGNMENT_BOTTOM
AlignmentLeft
ALIGNMENT_LEFT
AlignmentRight
ALIGNMENT_RIGHT
AlignmentTop
ALIGNMENT_TOP

Instances

Enum CreativeAssetAlignment Source # 
Eq CreativeAssetAlignment Source # 
Data CreativeAssetAlignment Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetAlignment -> c CreativeAssetAlignment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetAlignment #

toConstr :: CreativeAssetAlignment -> Constr #

dataTypeOf :: CreativeAssetAlignment -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetAlignment) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetAlignment) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetAlignment -> CreativeAssetAlignment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetAlignment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetAlignment -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetAlignment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetAlignment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetAlignment -> m CreativeAssetAlignment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetAlignment -> m CreativeAssetAlignment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetAlignment -> m CreativeAssetAlignment #

Ord CreativeAssetAlignment Source # 
Read CreativeAssetAlignment Source # 
Show CreativeAssetAlignment Source # 
Generic CreativeAssetAlignment Source # 
Hashable CreativeAssetAlignment Source # 
ToJSON CreativeAssetAlignment Source # 
FromJSON CreativeAssetAlignment Source # 
FromHttpApiData CreativeAssetAlignment Source # 
ToHttpApiData CreativeAssetAlignment Source # 
type Rep CreativeAssetAlignment Source # 
type Rep CreativeAssetAlignment = D1 (MetaData "CreativeAssetAlignment" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "AlignmentBottom" PrefixI False) U1) (C1 (MetaCons "AlignmentLeft" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AlignmentRight" PrefixI False) U1) (C1 (MetaCons "AlignmentTop" PrefixI False) U1)))

RemarketingListsListSortOrder

data RemarketingListsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

RLLSOAscending
ASCENDING
RLLSODescending
DESCENDING

Instances

Enum RemarketingListsListSortOrder Source # 
Eq RemarketingListsListSortOrder Source # 
Data RemarketingListsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RemarketingListsListSortOrder -> c RemarketingListsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RemarketingListsListSortOrder #

toConstr :: RemarketingListsListSortOrder -> Constr #

dataTypeOf :: RemarketingListsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RemarketingListsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RemarketingListsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> RemarketingListsListSortOrder -> RemarketingListsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RemarketingListsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RemarketingListsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> RemarketingListsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RemarketingListsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RemarketingListsListSortOrder -> m RemarketingListsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RemarketingListsListSortOrder -> m RemarketingListsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RemarketingListsListSortOrder -> m RemarketingListsListSortOrder #

Ord RemarketingListsListSortOrder Source # 
Read RemarketingListsListSortOrder Source # 
Show RemarketingListsListSortOrder Source # 
Generic RemarketingListsListSortOrder Source # 
Hashable RemarketingListsListSortOrder Source # 
ToJSON RemarketingListsListSortOrder Source # 
FromJSON RemarketingListsListSortOrder Source # 
FromHttpApiData RemarketingListsListSortOrder Source # 
ToHttpApiData RemarketingListsListSortOrder Source # 
type Rep RemarketingListsListSortOrder Source # 
type Rep RemarketingListsListSortOrder = D1 (MetaData "RemarketingListsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "RLLSOAscending" PrefixI False) U1) (C1 (MetaCons "RLLSODescending" PrefixI False) U1))

ReportPathToConversionCriteriaReportProperties

data ReportPathToConversionCriteriaReportProperties Source #

The properties of the report.

See: reportPathToConversionCriteriaReportProperties smart constructor.

Instances

Eq ReportPathToConversionCriteriaReportProperties Source # 
Data ReportPathToConversionCriteriaReportProperties Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportPathToConversionCriteriaReportProperties -> c ReportPathToConversionCriteriaReportProperties #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportPathToConversionCriteriaReportProperties #

toConstr :: ReportPathToConversionCriteriaReportProperties -> Constr #

dataTypeOf :: ReportPathToConversionCriteriaReportProperties -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportPathToConversionCriteriaReportProperties) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportPathToConversionCriteriaReportProperties) #

gmapT :: (forall b. Data b => b -> b) -> ReportPathToConversionCriteriaReportProperties -> ReportPathToConversionCriteriaReportProperties #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportPathToConversionCriteriaReportProperties -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportPathToConversionCriteriaReportProperties -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportPathToConversionCriteriaReportProperties -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportPathToConversionCriteriaReportProperties -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportPathToConversionCriteriaReportProperties -> m ReportPathToConversionCriteriaReportProperties #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportPathToConversionCriteriaReportProperties -> m ReportPathToConversionCriteriaReportProperties #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportPathToConversionCriteriaReportProperties -> m ReportPathToConversionCriteriaReportProperties #

Show ReportPathToConversionCriteriaReportProperties Source # 
Generic ReportPathToConversionCriteriaReportProperties Source # 
ToJSON ReportPathToConversionCriteriaReportProperties Source # 
FromJSON ReportPathToConversionCriteriaReportProperties Source # 
type Rep ReportPathToConversionCriteriaReportProperties Source # 
type Rep ReportPathToConversionCriteriaReportProperties = D1 (MetaData "ReportPathToConversionCriteriaReportProperties" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ReportPathToConversionCriteriaReportProperties'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rptccrpMaximumInteractionGap") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_rptccrpMaximumClickInteractions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) ((:*:) (S1 (MetaSel (Just Symbol "_rptccrpPivotOnInteractionPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_rptccrpMaximumImpressionInteractions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rptccrpIncludeUnattributedIPConversions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_rptccrpImpressionsLookbackWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) ((:*:) (S1 (MetaSel (Just Symbol "_rptccrpClicksLookbackWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_rptccrpIncludeUnattributedCookieConversions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_rptccrpIncludeAttributedIPConversions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))))

rptccrpMaximumInteractionGap :: Lens' ReportPathToConversionCriteriaReportProperties (Maybe Int32) Source #

The maximum amount of time that can take place between interactions (clicks or impressions) by the same user. Valid values: 1-90.

rptccrpMaximumClickInteractions :: Lens' ReportPathToConversionCriteriaReportProperties (Maybe Int32) Source #

The maximum number of click interactions to include in the report. Advertisers currently paying for E2C reports get up to 200 (100 clicks, 100 impressions). If another advertiser in your network is paying for E2C, you can have up to 5 total exposures per report.

rptccrpMaximumImpressionInteractions :: Lens' ReportPathToConversionCriteriaReportProperties (Maybe Int32) Source #

The maximum number of click interactions to include in the report. Advertisers currently paying for E2C reports get up to 200 (100 clicks, 100 impressions). If another advertiser in your network is paying for E2C, you can have up to 5 total exposures per report.

rptccrpIncludeUnattributedIPConversions :: Lens' ReportPathToConversionCriteriaReportProperties (Maybe Bool) Source #

Include conversions that have no associated cookies and no exposures. It’s therefore impossible to know how the user was exposed to your ads during the lookback window prior to a conversion.

rptccrpImpressionsLookbackWindow :: Lens' ReportPathToConversionCriteriaReportProperties (Maybe Int32) Source #

DFA checks to see if an impression interaction occurred within the specified period of time before a conversion. By default the value is pulled from Floodlight or you can manually enter a custom value. Valid values: 1-90.

rptccrpClicksLookbackWindow :: Lens' ReportPathToConversionCriteriaReportProperties (Maybe Int32) Source #

DFA checks to see if a click interaction occurred within the specified period of time before a conversion. By default the value is pulled from Floodlight or you can manually enter a custom value. Valid values: 1-90.

rptccrpIncludeUnattributedCookieConversions :: Lens' ReportPathToConversionCriteriaReportProperties (Maybe Bool) Source #

Include conversions of users with a DoubleClick cookie but without an exposure. That means the user did not click or see an ad from the advertiser within the Floodlight group, or that the interaction happened outside the lookback window.

UserRolePermissionsListResponse

data UserRolePermissionsListResponse Source #

User Role Permission List Response

See: userRolePermissionsListResponse smart constructor.

Instances

Eq UserRolePermissionsListResponse Source # 
Data UserRolePermissionsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserRolePermissionsListResponse -> c UserRolePermissionsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserRolePermissionsListResponse #

toConstr :: UserRolePermissionsListResponse -> Constr #

dataTypeOf :: UserRolePermissionsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserRolePermissionsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserRolePermissionsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> UserRolePermissionsListResponse -> UserRolePermissionsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserRolePermissionsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserRolePermissionsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserRolePermissionsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserRolePermissionsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserRolePermissionsListResponse -> m UserRolePermissionsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRolePermissionsListResponse -> m UserRolePermissionsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRolePermissionsListResponse -> m UserRolePermissionsListResponse #

Show UserRolePermissionsListResponse Source # 
Generic UserRolePermissionsListResponse Source # 
ToJSON UserRolePermissionsListResponse Source # 
FromJSON UserRolePermissionsListResponse Source # 
type Rep UserRolePermissionsListResponse Source # 
type Rep UserRolePermissionsListResponse = D1 (MetaData "UserRolePermissionsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "UserRolePermissionsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_urplrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_urplrUserRolePermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UserRolePermission])))))

userRolePermissionsListResponse :: UserRolePermissionsListResponse Source #

Creates a value of UserRolePermissionsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

urplrKind :: Lens' UserRolePermissionsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#userRolePermissionsListResponse".

PlacementGroupsListPricingTypes

data PlacementGroupsListPricingTypes Source #

Select only placement groups with these pricing types.

Constructors

PGLPTPricingTypeCpa
PRICING_TYPE_CPA
PGLPTPricingTypeCpc
PRICING_TYPE_CPC
PGLPTPricingTypeCpm
PRICING_TYPE_CPM
PGLPTPricingTypeFlatRateClicks
PRICING_TYPE_FLAT_RATE_CLICKS
PGLPTPricingTypeFlatRateImpressions
PRICING_TYPE_FLAT_RATE_IMPRESSIONS

Instances

Enum PlacementGroupsListPricingTypes Source # 
Eq PlacementGroupsListPricingTypes Source # 
Data PlacementGroupsListPricingTypes Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementGroupsListPricingTypes -> c PlacementGroupsListPricingTypes #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementGroupsListPricingTypes #

toConstr :: PlacementGroupsListPricingTypes -> Constr #

dataTypeOf :: PlacementGroupsListPricingTypes -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementGroupsListPricingTypes) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementGroupsListPricingTypes) #

gmapT :: (forall b. Data b => b -> b) -> PlacementGroupsListPricingTypes -> PlacementGroupsListPricingTypes #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroupsListPricingTypes -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroupsListPricingTypes -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementGroupsListPricingTypes -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementGroupsListPricingTypes -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementGroupsListPricingTypes -> m PlacementGroupsListPricingTypes #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroupsListPricingTypes -> m PlacementGroupsListPricingTypes #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroupsListPricingTypes -> m PlacementGroupsListPricingTypes #

Ord PlacementGroupsListPricingTypes Source # 
Read PlacementGroupsListPricingTypes Source # 
Show PlacementGroupsListPricingTypes Source # 
Generic PlacementGroupsListPricingTypes Source # 
Hashable PlacementGroupsListPricingTypes Source # 
ToJSON PlacementGroupsListPricingTypes Source # 
FromJSON PlacementGroupsListPricingTypes Source # 
FromHttpApiData PlacementGroupsListPricingTypes Source # 
ToHttpApiData PlacementGroupsListPricingTypes Source # 
type Rep PlacementGroupsListPricingTypes Source # 
type Rep PlacementGroupsListPricingTypes = D1 (MetaData "PlacementGroupsListPricingTypes" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "PGLPTPricingTypeCpa" PrefixI False) U1) (C1 (MetaCons "PGLPTPricingTypeCpc" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PGLPTPricingTypeCpm" PrefixI False) U1) ((:+:) (C1 (MetaCons "PGLPTPricingTypeFlatRateClicks" PrefixI False) U1) (C1 (MetaCons "PGLPTPricingTypeFlatRateImpressions" PrefixI False) U1))))

DynamicTargetingKeysDeleteObjectType

data DynamicTargetingKeysDeleteObjectType Source #

Type of the object of this dynamic targeting key. This is a required field.

Constructors

DTKDOTObjectAd
OBJECT_AD
DTKDOTObjectAdvertiser
OBJECT_ADVERTISER
DTKDOTObjectCreative
OBJECT_CREATIVE
DTKDOTObjectPlacement
OBJECT_PLACEMENT

Instances

Enum DynamicTargetingKeysDeleteObjectType Source # 
Eq DynamicTargetingKeysDeleteObjectType Source # 
Data DynamicTargetingKeysDeleteObjectType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DynamicTargetingKeysDeleteObjectType -> c DynamicTargetingKeysDeleteObjectType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DynamicTargetingKeysDeleteObjectType #

toConstr :: DynamicTargetingKeysDeleteObjectType -> Constr #

dataTypeOf :: DynamicTargetingKeysDeleteObjectType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DynamicTargetingKeysDeleteObjectType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DynamicTargetingKeysDeleteObjectType) #

gmapT :: (forall b. Data b => b -> b) -> DynamicTargetingKeysDeleteObjectType -> DynamicTargetingKeysDeleteObjectType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DynamicTargetingKeysDeleteObjectType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DynamicTargetingKeysDeleteObjectType -> r #

gmapQ :: (forall d. Data d => d -> u) -> DynamicTargetingKeysDeleteObjectType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DynamicTargetingKeysDeleteObjectType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DynamicTargetingKeysDeleteObjectType -> m DynamicTargetingKeysDeleteObjectType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DynamicTargetingKeysDeleteObjectType -> m DynamicTargetingKeysDeleteObjectType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DynamicTargetingKeysDeleteObjectType -> m DynamicTargetingKeysDeleteObjectType #

Ord DynamicTargetingKeysDeleteObjectType Source # 
Read DynamicTargetingKeysDeleteObjectType Source # 
Show DynamicTargetingKeysDeleteObjectType Source # 
Generic DynamicTargetingKeysDeleteObjectType Source # 
Hashable DynamicTargetingKeysDeleteObjectType Source # 
ToJSON DynamicTargetingKeysDeleteObjectType Source # 
FromJSON DynamicTargetingKeysDeleteObjectType Source # 
FromHttpApiData DynamicTargetingKeysDeleteObjectType Source # 
ToHttpApiData DynamicTargetingKeysDeleteObjectType Source # 
type Rep DynamicTargetingKeysDeleteObjectType Source # 
type Rep DynamicTargetingKeysDeleteObjectType = D1 (MetaData "DynamicTargetingKeysDeleteObjectType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "DTKDOTObjectAd" PrefixI False) U1) (C1 (MetaCons "DTKDOTObjectAdvertiser" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DTKDOTObjectCreative" PrefixI False) U1) (C1 (MetaCons "DTKDOTObjectPlacement" PrefixI False) U1)))

AccountActiveAdsLimitTier

data AccountActiveAdsLimitTier Source #

Maximum number of active ads allowed for this account.

Constructors

AAALTActiveAdsTier100K
ACTIVE_ADS_TIER_100K
AAALTActiveAdsTier200K
ACTIVE_ADS_TIER_200K
AAALTActiveAdsTier300K
ACTIVE_ADS_TIER_300K
AAALTActiveAdsTier40K
ACTIVE_ADS_TIER_40K
AAALTActiveAdsTier75K
ACTIVE_ADS_TIER_75K

Instances

Enum AccountActiveAdsLimitTier Source # 
Eq AccountActiveAdsLimitTier Source # 
Data AccountActiveAdsLimitTier Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountActiveAdsLimitTier -> c AccountActiveAdsLimitTier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountActiveAdsLimitTier #

toConstr :: AccountActiveAdsLimitTier -> Constr #

dataTypeOf :: AccountActiveAdsLimitTier -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountActiveAdsLimitTier) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountActiveAdsLimitTier) #

gmapT :: (forall b. Data b => b -> b) -> AccountActiveAdsLimitTier -> AccountActiveAdsLimitTier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountActiveAdsLimitTier -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountActiveAdsLimitTier -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountActiveAdsLimitTier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountActiveAdsLimitTier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountActiveAdsLimitTier -> m AccountActiveAdsLimitTier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountActiveAdsLimitTier -> m AccountActiveAdsLimitTier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountActiveAdsLimitTier -> m AccountActiveAdsLimitTier #

Ord AccountActiveAdsLimitTier Source # 
Read AccountActiveAdsLimitTier Source # 
Show AccountActiveAdsLimitTier Source # 
Generic AccountActiveAdsLimitTier Source # 
Hashable AccountActiveAdsLimitTier Source # 
ToJSON AccountActiveAdsLimitTier Source # 
FromJSON AccountActiveAdsLimitTier Source # 
FromHttpApiData AccountActiveAdsLimitTier Source # 
ToHttpApiData AccountActiveAdsLimitTier Source # 
type Rep AccountActiveAdsLimitTier Source # 
type Rep AccountActiveAdsLimitTier = D1 (MetaData "AccountActiveAdsLimitTier" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "AAALTActiveAdsTier100K" PrefixI False) U1) (C1 (MetaCons "AAALTActiveAdsTier200K" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AAALTActiveAdsTier300K" PrefixI False) U1) ((:+:) (C1 (MetaCons "AAALTActiveAdsTier40K" PrefixI False) U1) (C1 (MetaCons "AAALTActiveAdsTier75K" PrefixI False) U1))))

AccountsListSortOrder

data AccountsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

AAscending
ASCENDING
ADescending
DESCENDING

Instances

Enum AccountsListSortOrder Source # 
Eq AccountsListSortOrder Source # 
Data AccountsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountsListSortOrder -> c AccountsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountsListSortOrder #

toConstr :: AccountsListSortOrder -> Constr #

dataTypeOf :: AccountsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> AccountsListSortOrder -> AccountsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountsListSortOrder -> m AccountsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountsListSortOrder -> m AccountsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountsListSortOrder -> m AccountsListSortOrder #

Ord AccountsListSortOrder Source # 
Read AccountsListSortOrder Source # 
Show AccountsListSortOrder Source # 
Generic AccountsListSortOrder Source # 
Hashable AccountsListSortOrder Source # 
ToJSON AccountsListSortOrder Source # 
FromJSON AccountsListSortOrder Source # 
FromHttpApiData AccountsListSortOrder Source # 
ToHttpApiData AccountsListSortOrder Source # 
type Rep AccountsListSortOrder Source # 
type Rep AccountsListSortOrder = D1 (MetaData "AccountsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "AAscending" PrefixI False) U1) (C1 (MetaCons "ADescending" PrefixI False) U1))

PlacementGroupsListResponse

data PlacementGroupsListResponse Source #

Placement Group List Response

See: placementGroupsListResponse smart constructor.

Instances

Eq PlacementGroupsListResponse Source # 
Data PlacementGroupsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementGroupsListResponse -> c PlacementGroupsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementGroupsListResponse #

toConstr :: PlacementGroupsListResponse -> Constr #

dataTypeOf :: PlacementGroupsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementGroupsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementGroupsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> PlacementGroupsListResponse -> PlacementGroupsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroupsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroupsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementGroupsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementGroupsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementGroupsListResponse -> m PlacementGroupsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroupsListResponse -> m PlacementGroupsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroupsListResponse -> m PlacementGroupsListResponse #

Show PlacementGroupsListResponse Source # 
Generic PlacementGroupsListResponse Source # 
ToJSON PlacementGroupsListResponse Source # 
FromJSON PlacementGroupsListResponse Source # 
type Rep PlacementGroupsListResponse Source # 
type Rep PlacementGroupsListResponse = D1 (MetaData "PlacementGroupsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PlacementGroupsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pglrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_pglrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_pglrPlacementGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PlacementGroup]))))))

placementGroupsListResponse :: PlacementGroupsListResponse Source #

Creates a value of PlacementGroupsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pglrNextPageToken :: Lens' PlacementGroupsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

pglrKind :: Lens' PlacementGroupsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#placementGroupsListResponse".

MobileCarrier

data MobileCarrier Source #

Contains information about a mobile carrier that can be targeted by ads.

See: mobileCarrier smart constructor.

Instances

Eq MobileCarrier Source # 
Data MobileCarrier Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MobileCarrier -> c MobileCarrier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MobileCarrier #

toConstr :: MobileCarrier -> Constr #

dataTypeOf :: MobileCarrier -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MobileCarrier) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MobileCarrier) #

gmapT :: (forall b. Data b => b -> b) -> MobileCarrier -> MobileCarrier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MobileCarrier -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MobileCarrier -> r #

gmapQ :: (forall d. Data d => d -> u) -> MobileCarrier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MobileCarrier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MobileCarrier -> m MobileCarrier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MobileCarrier -> m MobileCarrier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MobileCarrier -> m MobileCarrier #

Show MobileCarrier Source # 
Generic MobileCarrier Source # 

Associated Types

type Rep MobileCarrier :: * -> * #

ToJSON MobileCarrier Source # 
FromJSON MobileCarrier Source # 
type Rep MobileCarrier Source # 
type Rep MobileCarrier = D1 (MetaData "MobileCarrier" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "MobileCarrier'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_mcKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_mcName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_mcCountryCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_mcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_mcCountryDartId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))))

mobileCarrier :: MobileCarrier Source #

Creates a value of MobileCarrier with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

mcKind :: Lens' MobileCarrier Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#mobileCarrier".

mcName :: Lens' MobileCarrier (Maybe Text) Source #

Name of this mobile carrier.

mcCountryCode :: Lens' MobileCarrier (Maybe Text) Source #

Country code of the country to which this mobile carrier belongs.

mcId :: Lens' MobileCarrier (Maybe Int64) Source #

ID of this mobile carrier.

mcCountryDartId :: Lens' MobileCarrier (Maybe Int64) Source #

DART ID of the country to which this mobile carrier belongs.

LandingPage

data LandingPage Source #

Contains information about where a user's browser is taken after the user clicks an ad.

See: landingPage smart constructor.

Instances

Eq LandingPage Source # 
Data LandingPage Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LandingPage -> c LandingPage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LandingPage #

toConstr :: LandingPage -> Constr #

dataTypeOf :: LandingPage -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LandingPage) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LandingPage) #

gmapT :: (forall b. Data b => b -> b) -> LandingPage -> LandingPage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LandingPage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LandingPage -> r #

gmapQ :: (forall d. Data d => d -> u) -> LandingPage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LandingPage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LandingPage -> m LandingPage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LandingPage -> m LandingPage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LandingPage -> m LandingPage #

Show LandingPage Source # 
Generic LandingPage Source # 

Associated Types

type Rep LandingPage :: * -> * #

ToJSON LandingPage Source # 
FromJSON LandingPage Source # 
type Rep LandingPage Source # 
type Rep LandingPage = D1 (MetaData "LandingPage" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "LandingPage'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_lpKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_lpDefault") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_lpURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_lpName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_lpId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))))

landingPage :: LandingPage Source #

Creates a value of LandingPage with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lpKind :: Lens' LandingPage Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#landingPage".

lpDefault :: Lens' LandingPage (Maybe Bool) Source #

Whether or not this landing page will be assigned to any ads or creatives that do not have a landing page assigned explicitly. Only one default landing page is allowed per campaign.

lpURL :: Lens' LandingPage (Maybe Text) Source #

URL of this landing page. This is a required field.

lpName :: Lens' LandingPage (Maybe Text) Source #

Name of this landing page. This is a required field. It must be less than 256 characters long, and must be unique among landing pages of the same campaign.

lpId :: Lens' LandingPage (Maybe Int64) Source #

ID of this landing page. This is a read-only, auto-generated field.

ConnectionTypesListResponse

data ConnectionTypesListResponse Source #

Connection Type List Response

See: connectionTypesListResponse smart constructor.

Instances

Eq ConnectionTypesListResponse Source # 
Data ConnectionTypesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConnectionTypesListResponse -> c ConnectionTypesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConnectionTypesListResponse #

toConstr :: ConnectionTypesListResponse -> Constr #

dataTypeOf :: ConnectionTypesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConnectionTypesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConnectionTypesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> ConnectionTypesListResponse -> ConnectionTypesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConnectionTypesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConnectionTypesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConnectionTypesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConnectionTypesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConnectionTypesListResponse -> m ConnectionTypesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConnectionTypesListResponse -> m ConnectionTypesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConnectionTypesListResponse -> m ConnectionTypesListResponse #

Show ConnectionTypesListResponse Source # 
Generic ConnectionTypesListResponse Source # 
ToJSON ConnectionTypesListResponse Source # 
FromJSON ConnectionTypesListResponse Source # 
type Rep ConnectionTypesListResponse Source # 
type Rep ConnectionTypesListResponse = D1 (MetaData "ConnectionTypesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ConnectionTypesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ctlrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_ctlrConnectionTypes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ConnectionType])))))

connectionTypesListResponse :: ConnectionTypesListResponse Source #

Creates a value of ConnectionTypesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ctlrKind :: Lens' ConnectionTypesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#connectionTypesListResponse".

ctlrConnectionTypes :: Lens' ConnectionTypesListResponse [ConnectionType] Source #

Collection of connection types such as broadband and mobile.

OrdersListResponse

data OrdersListResponse Source #

Order List Response

See: ordersListResponse smart constructor.

Instances

Eq OrdersListResponse Source # 
Data OrdersListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrdersListResponse -> c OrdersListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrdersListResponse #

toConstr :: OrdersListResponse -> Constr #

dataTypeOf :: OrdersListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrdersListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrdersListResponse) #

gmapT :: (forall b. Data b => b -> b) -> OrdersListResponse -> OrdersListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrdersListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrdersListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrdersListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrdersListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrdersListResponse -> m OrdersListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrdersListResponse -> m OrdersListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrdersListResponse -> m OrdersListResponse #

Show OrdersListResponse Source # 
Generic OrdersListResponse Source # 
ToJSON OrdersListResponse Source # 
FromJSON OrdersListResponse Source # 
type Rep OrdersListResponse Source # 
type Rep OrdersListResponse = D1 (MetaData "OrdersListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "OrdersListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_olrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_olrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_olrOrders") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Order]))))))

ordersListResponse :: OrdersListResponse Source #

Creates a value of OrdersListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

olrNextPageToken :: Lens' OrdersListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

olrKind :: Lens' OrdersListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#ordersListResponse".

ReportList

data ReportList Source #

Represents the list of reports.

See: reportList smart constructor.

Instances

Eq ReportList Source # 
Data ReportList Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportList -> c ReportList #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportList #

toConstr :: ReportList -> Constr #

dataTypeOf :: ReportList -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportList) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportList) #

gmapT :: (forall b. Data b => b -> b) -> ReportList -> ReportList #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportList -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportList -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportList -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportList -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportList -> m ReportList #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportList -> m ReportList #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportList -> m ReportList #

Show ReportList Source # 
Generic ReportList Source # 

Associated Types

type Rep ReportList :: * -> * #

ToJSON ReportList Source # 
FromJSON ReportList Source # 
type Rep ReportList Source # 
type Rep ReportList = D1 (MetaData "ReportList" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ReportList'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_repEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_repNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_repKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_repItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Report]))))))

reportList :: ReportList Source #

Creates a value of ReportList with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

repEtag :: Lens' ReportList (Maybe Text) Source #

The eTag of this response for caching purposes.

repNextPageToken :: Lens' ReportList (Maybe Text) Source #

Continuation token used to page through reports. To retrieve the next page of results, set the next request's "pageToken" to the value of this field. The page token is only valid for a limited amount of time and should not be persisted.

repKind :: Lens' ReportList Text Source #

The kind of list this is, in this case dfareporting#reportList.

repItems :: Lens' ReportList [Report] Source #

The reports returned in this response.

CreativeGroup

data CreativeGroup Source #

Contains properties of a creative group.

See: creativeGroup smart constructor.

Instances

Eq CreativeGroup Source # 
Data CreativeGroup Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeGroup -> c CreativeGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeGroup #

toConstr :: CreativeGroup -> Constr #

dataTypeOf :: CreativeGroup -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeGroup) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeGroup) #

gmapT :: (forall b. Data b => b -> b) -> CreativeGroup -> CreativeGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeGroup -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeGroup -> m CreativeGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeGroup -> m CreativeGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeGroup -> m CreativeGroup #

Show CreativeGroup Source # 
Generic CreativeGroup Source # 

Associated Types

type Rep CreativeGroup :: * -> * #

ToJSON CreativeGroup Source # 
FromJSON CreativeGroup Source # 
type Rep CreativeGroup Source # 

creativeGroup :: CreativeGroup Source #

Creates a value of CreativeGroup with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cgKind :: Lens' CreativeGroup Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#creativeGroup".

cgAdvertiserId :: Lens' CreativeGroup (Maybe Int64) Source #

Advertiser ID of this creative group. This is a required field on insertion.

cgAdvertiserIdDimensionValue :: Lens' CreativeGroup (Maybe DimensionValue) Source #

Dimension value for the ID of the advertiser. This is a read-only, auto-generated field.

cgGroupNumber :: Lens' CreativeGroup (Maybe Int32) Source #

Subgroup of the creative group. Assign your creative groups to one of the following subgroups in order to filter or manage them more easily. This field is required on insertion and is read-only after insertion. Acceptable values are: - 1 - 2

cgAccountId :: Lens' CreativeGroup (Maybe Int64) Source #

Account ID of this creative group. This is a read-only field that can be left blank.

cgName :: Lens' CreativeGroup (Maybe Text) Source #

Name of this creative group. This is a required field and must be less than 256 characters long and unique among creative groups of the same advertiser.

cgId :: Lens' CreativeGroup (Maybe Int64) Source #

ID of this creative group. This is a read-only, auto-generated field.

cgSubAccountId :: Lens' CreativeGroup (Maybe Int64) Source #

Subaccount ID of this creative group. This is a read-only field that can be left blank.

SubAccountsListSortField

data SubAccountsListSortField Source #

Field by which to sort the list.

Constructors

SALSFID
ID
SALSFName
NAME

Instances

Enum SubAccountsListSortField Source # 
Eq SubAccountsListSortField Source # 
Data SubAccountsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SubAccountsListSortField -> c SubAccountsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SubAccountsListSortField #

toConstr :: SubAccountsListSortField -> Constr #

dataTypeOf :: SubAccountsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SubAccountsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SubAccountsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> SubAccountsListSortField -> SubAccountsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SubAccountsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SubAccountsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> SubAccountsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SubAccountsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SubAccountsListSortField -> m SubAccountsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SubAccountsListSortField -> m SubAccountsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SubAccountsListSortField -> m SubAccountsListSortField #

Ord SubAccountsListSortField Source # 
Read SubAccountsListSortField Source # 
Show SubAccountsListSortField Source # 
Generic SubAccountsListSortField Source # 
Hashable SubAccountsListSortField Source # 
ToJSON SubAccountsListSortField Source # 
FromJSON SubAccountsListSortField Source # 
FromHttpApiData SubAccountsListSortField Source # 
ToHttpApiData SubAccountsListSortField Source # 
type Rep SubAccountsListSortField Source # 
type Rep SubAccountsListSortField = D1 (MetaData "SubAccountsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "SALSFID" PrefixI False) U1) (C1 (MetaCons "SALSFName" PrefixI False) U1))

CampaignCreativeAssociation

data CampaignCreativeAssociation Source #

Identifies a creative which has been associated with a given campaign.

See: campaignCreativeAssociation smart constructor.

Instances

Eq CampaignCreativeAssociation Source # 
Data CampaignCreativeAssociation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CampaignCreativeAssociation -> c CampaignCreativeAssociation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CampaignCreativeAssociation #

toConstr :: CampaignCreativeAssociation -> Constr #

dataTypeOf :: CampaignCreativeAssociation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CampaignCreativeAssociation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CampaignCreativeAssociation) #

gmapT :: (forall b. Data b => b -> b) -> CampaignCreativeAssociation -> CampaignCreativeAssociation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CampaignCreativeAssociation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CampaignCreativeAssociation -> r #

gmapQ :: (forall d. Data d => d -> u) -> CampaignCreativeAssociation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CampaignCreativeAssociation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CampaignCreativeAssociation -> m CampaignCreativeAssociation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignCreativeAssociation -> m CampaignCreativeAssociation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignCreativeAssociation -> m CampaignCreativeAssociation #

Show CampaignCreativeAssociation Source # 
Generic CampaignCreativeAssociation Source # 
ToJSON CampaignCreativeAssociation Source # 
FromJSON CampaignCreativeAssociation Source # 
type Rep CampaignCreativeAssociation Source # 
type Rep CampaignCreativeAssociation = D1 (MetaData "CampaignCreativeAssociation" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CampaignCreativeAssociation'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ccaKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_ccaCreativeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))

campaignCreativeAssociation :: CampaignCreativeAssociation Source #

Creates a value of CampaignCreativeAssociation with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ccaKind :: Lens' CampaignCreativeAssociation Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#campaignCreativeAssociation".

ccaCreativeId :: Lens' CampaignCreativeAssociation (Maybe Int64) Source #

ID of the creative associated with the campaign. This is a required field.

ConversionStatus

data ConversionStatus Source #

The original conversion that was inserted and whether there were any errors.

See: conversionStatus smart constructor.

Instances

Eq ConversionStatus Source # 
Data ConversionStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConversionStatus -> c ConversionStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConversionStatus #

toConstr :: ConversionStatus -> Constr #

dataTypeOf :: ConversionStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConversionStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConversionStatus) #

gmapT :: (forall b. Data b => b -> b) -> ConversionStatus -> ConversionStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConversionStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConversionStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConversionStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConversionStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConversionStatus -> m ConversionStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConversionStatus -> m ConversionStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConversionStatus -> m ConversionStatus #

Show ConversionStatus Source # 
Generic ConversionStatus Source # 
ToJSON ConversionStatus Source # 
FromJSON ConversionStatus Source # 
type Rep ConversionStatus Source # 
type Rep ConversionStatus = D1 (MetaData "ConversionStatus" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ConversionStatus'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_csKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_csConversion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Conversion))) (S1 (MetaSel (Just Symbol "_csErrors") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ConversionError]))))))

conversionStatus :: ConversionStatus Source #

Creates a value of ConversionStatus with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

csKind :: Lens' ConversionStatus Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#conversionStatus".

csConversion :: Lens' ConversionStatus (Maybe Conversion) Source #

The original conversion that was inserted.

csErrors :: Lens' ConversionStatus [ConversionError] Source #

A list of errors related to this conversion.

LookbackConfiguration

data LookbackConfiguration Source #

Lookback configuration settings.

See: lookbackConfiguration smart constructor.

Instances

Eq LookbackConfiguration Source # 
Data LookbackConfiguration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LookbackConfiguration -> c LookbackConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LookbackConfiguration #

toConstr :: LookbackConfiguration -> Constr #

dataTypeOf :: LookbackConfiguration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LookbackConfiguration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LookbackConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> LookbackConfiguration -> LookbackConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LookbackConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LookbackConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> LookbackConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LookbackConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LookbackConfiguration -> m LookbackConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LookbackConfiguration -> m LookbackConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LookbackConfiguration -> m LookbackConfiguration #

Show LookbackConfiguration Source # 
Generic LookbackConfiguration Source # 
ToJSON LookbackConfiguration Source # 
FromJSON LookbackConfiguration Source # 
type Rep LookbackConfiguration Source # 
type Rep LookbackConfiguration = D1 (MetaData "LookbackConfiguration" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "LookbackConfiguration'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_lcClickDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_lcPostImpressionActivitiesDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

lookbackConfiguration :: LookbackConfiguration Source #

Creates a value of LookbackConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lcClickDuration :: Lens' LookbackConfiguration (Maybe Int32) Source #

Lookback window, in days, from the last time a given user clicked on one of your ads. If you enter 0, clicks will not be considered as triggering events for floodlight tracking. If you leave this field blank, the default value for your account will be used.

lcPostImpressionActivitiesDuration :: Lens' LookbackConfiguration (Maybe Int32) Source #

Lookback window, in days, from the last time a given user viewed one of your ads. If you enter 0, impressions will not be considered as triggering events for floodlight tracking. If you leave this field blank, the default value for your account will be used.

AdsListSortField

data AdsListSortField Source #

Field by which to sort the list.

Constructors

ALSFID
ID
ALSFName
NAME

Instances

Enum AdsListSortField Source # 
Eq AdsListSortField Source # 
Data AdsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdsListSortField -> c AdsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdsListSortField #

toConstr :: AdsListSortField -> Constr #

dataTypeOf :: AdsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> AdsListSortField -> AdsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdsListSortField -> m AdsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdsListSortField -> m AdsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdsListSortField -> m AdsListSortField #

Ord AdsListSortField Source # 
Read AdsListSortField Source # 
Show AdsListSortField Source # 
Generic AdsListSortField Source # 
Hashable AdsListSortField Source # 
ToJSON AdsListSortField Source # 
FromJSON AdsListSortField Source # 
FromHttpApiData AdsListSortField Source # 
ToHttpApiData AdsListSortField Source # 
type Rep AdsListSortField Source # 
type Rep AdsListSortField = D1 (MetaData "AdsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ALSFID" PrefixI False) U1) (C1 (MetaCons "ALSFName" PrefixI False) U1))

ProjectsListSortField

data ProjectsListSortField Source #

Field by which to sort the list.

Constructors

PID
ID
PName
NAME

Instances

Enum ProjectsListSortField Source # 
Eq ProjectsListSortField Source # 
Data ProjectsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProjectsListSortField -> c ProjectsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProjectsListSortField #

toConstr :: ProjectsListSortField -> Constr #

dataTypeOf :: ProjectsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProjectsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProjectsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> ProjectsListSortField -> ProjectsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProjectsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProjectsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProjectsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProjectsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProjectsListSortField -> m ProjectsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProjectsListSortField -> m ProjectsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProjectsListSortField -> m ProjectsListSortField #

Ord ProjectsListSortField Source # 
Read ProjectsListSortField Source # 
Show ProjectsListSortField Source # 
Generic ProjectsListSortField Source # 
Hashable ProjectsListSortField Source # 
ToJSON ProjectsListSortField Source # 
FromJSON ProjectsListSortField Source # 
FromHttpApiData ProjectsListSortField Source # 
ToHttpApiData ProjectsListSortField Source # 
type Rep ProjectsListSortField Source # 
type Rep ProjectsListSortField = D1 (MetaData "ProjectsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PID" PrefixI False) U1) (C1 (MetaCons "PName" PrefixI False) U1))

FloodlightActivityPublisherDynamicTag

data FloodlightActivityPublisherDynamicTag Source #

Publisher Dynamic Tag

See: floodlightActivityPublisherDynamicTag smart constructor.

Instances

Eq FloodlightActivityPublisherDynamicTag Source # 
Data FloodlightActivityPublisherDynamicTag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivityPublisherDynamicTag -> c FloodlightActivityPublisherDynamicTag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivityPublisherDynamicTag #

toConstr :: FloodlightActivityPublisherDynamicTag -> Constr #

dataTypeOf :: FloodlightActivityPublisherDynamicTag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivityPublisherDynamicTag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivityPublisherDynamicTag) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivityPublisherDynamicTag -> FloodlightActivityPublisherDynamicTag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityPublisherDynamicTag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityPublisherDynamicTag -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivityPublisherDynamicTag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivityPublisherDynamicTag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivityPublisherDynamicTag -> m FloodlightActivityPublisherDynamicTag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityPublisherDynamicTag -> m FloodlightActivityPublisherDynamicTag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityPublisherDynamicTag -> m FloodlightActivityPublisherDynamicTag #

Show FloodlightActivityPublisherDynamicTag Source # 
Generic FloodlightActivityPublisherDynamicTag Source # 
ToJSON FloodlightActivityPublisherDynamicTag Source # 
FromJSON FloodlightActivityPublisherDynamicTag Source # 
type Rep FloodlightActivityPublisherDynamicTag Source # 
type Rep FloodlightActivityPublisherDynamicTag = D1 (MetaData "FloodlightActivityPublisherDynamicTag" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FloodlightActivityPublisherDynamicTag'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_fapdtClickThrough") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_fapdtSiteIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_fapdtDynamicTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FloodlightActivityDynamicTag))))) ((:*:) (S1 (MetaSel (Just Symbol "_fapdtDirectorySiteId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_fapdtSiteId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_fapdtViewThrough") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))))

fapdtClickThrough :: Lens' FloodlightActivityPublisherDynamicTag (Maybe Bool) Source #

Whether this tag is applicable only for click-throughs.

fapdtSiteIdDimensionValue :: Lens' FloodlightActivityPublisherDynamicTag (Maybe DimensionValue) Source #

Dimension value for the ID of the site. This is a read-only, auto-generated field.

fapdtDirectorySiteId :: Lens' FloodlightActivityPublisherDynamicTag (Maybe Int64) Source #

Directory site ID of this dynamic tag. This is a write-only field that can be used as an alternative to the siteId field. When this resource is retrieved, only the siteId field will be populated.

fapdtViewThrough :: Lens' FloodlightActivityPublisherDynamicTag (Maybe Bool) Source #

Whether this tag is applicable only for view-throughs.

AdsListType

data AdsListType Source #

Select only ads with these types.

Constructors

AdServingClickTracker
AD_SERVING_CLICK_TRACKER
AdServingDefaultAd
AD_SERVING_DEFAULT_AD
AdServingStandardAd
AD_SERVING_STANDARD_AD
AdServingTracking
AD_SERVING_TRACKING

Instances

Enum AdsListType Source # 
Eq AdsListType Source # 
Data AdsListType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdsListType -> c AdsListType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdsListType #

toConstr :: AdsListType -> Constr #

dataTypeOf :: AdsListType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdsListType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdsListType) #

gmapT :: (forall b. Data b => b -> b) -> AdsListType -> AdsListType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdsListType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdsListType -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdsListType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdsListType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdsListType -> m AdsListType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdsListType -> m AdsListType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdsListType -> m AdsListType #

Ord AdsListType Source # 
Read AdsListType Source # 
Show AdsListType Source # 
Generic AdsListType Source # 

Associated Types

type Rep AdsListType :: * -> * #

Hashable AdsListType Source # 
ToJSON AdsListType Source # 
FromJSON AdsListType Source # 
FromHttpApiData AdsListType Source # 
ToHttpApiData AdsListType Source # 
type Rep AdsListType Source # 
type Rep AdsListType = D1 (MetaData "AdsListType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "AdServingClickTracker" PrefixI False) U1) (C1 (MetaCons "AdServingDefaultAd" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AdServingStandardAd" PrefixI False) U1) (C1 (MetaCons "AdServingTracking" PrefixI False) U1)))

AccountActiveAdSummary

data AccountActiveAdSummary Source #

Gets a summary of active ads in an account.

See: accountActiveAdSummary smart constructor.

Instances

Eq AccountActiveAdSummary Source # 
Data AccountActiveAdSummary Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountActiveAdSummary -> c AccountActiveAdSummary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountActiveAdSummary #

toConstr :: AccountActiveAdSummary -> Constr #

dataTypeOf :: AccountActiveAdSummary -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountActiveAdSummary) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountActiveAdSummary) #

gmapT :: (forall b. Data b => b -> b) -> AccountActiveAdSummary -> AccountActiveAdSummary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountActiveAdSummary -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountActiveAdSummary -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountActiveAdSummary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountActiveAdSummary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountActiveAdSummary -> m AccountActiveAdSummary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountActiveAdSummary -> m AccountActiveAdSummary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountActiveAdSummary -> m AccountActiveAdSummary #

Show AccountActiveAdSummary Source # 
Generic AccountActiveAdSummary Source # 
ToJSON AccountActiveAdSummary Source # 
FromJSON AccountActiveAdSummary Source # 
type Rep AccountActiveAdSummary Source # 
type Rep AccountActiveAdSummary = D1 (MetaData "AccountActiveAdSummary" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AccountActiveAdSummary'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aaasAvailableAds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_aaasKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_aaasAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_aaasActiveAds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_aaasActiveAdsLimitTier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AccountActiveAdSummaryActiveAdsLimitTier)))))))

accountActiveAdSummary :: AccountActiveAdSummary Source #

Creates a value of AccountActiveAdSummary with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

aaasAvailableAds :: Lens' AccountActiveAdSummary (Maybe Int64) Source #

Ads that can be activated for the account.

aaasKind :: Lens' AccountActiveAdSummary Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#accountActiveAdSummary".

aaasActiveAds :: Lens' AccountActiveAdSummary (Maybe Int64) Source #

Ads that have been activated for the account

CreativeOptimizationConfigurationOptimizationModel

data CreativeOptimizationConfigurationOptimizationModel Source #

Optimization model for this configuration.

Constructors

Click
CLICK
PostClick
POST_CLICK
PostClickAndImpression
POST_CLICK_AND_IMPRESSION
PostImpression
POST_IMPRESSION
VideoCompletion
VIDEO_COMPLETION

Instances

Enum CreativeOptimizationConfigurationOptimizationModel Source # 
Eq CreativeOptimizationConfigurationOptimizationModel Source # 
Data CreativeOptimizationConfigurationOptimizationModel Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeOptimizationConfigurationOptimizationModel -> c CreativeOptimizationConfigurationOptimizationModel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeOptimizationConfigurationOptimizationModel #

toConstr :: CreativeOptimizationConfigurationOptimizationModel -> Constr #

dataTypeOf :: CreativeOptimizationConfigurationOptimizationModel -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeOptimizationConfigurationOptimizationModel) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeOptimizationConfigurationOptimizationModel) #

gmapT :: (forall b. Data b => b -> b) -> CreativeOptimizationConfigurationOptimizationModel -> CreativeOptimizationConfigurationOptimizationModel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeOptimizationConfigurationOptimizationModel -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeOptimizationConfigurationOptimizationModel -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeOptimizationConfigurationOptimizationModel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeOptimizationConfigurationOptimizationModel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeOptimizationConfigurationOptimizationModel -> m CreativeOptimizationConfigurationOptimizationModel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeOptimizationConfigurationOptimizationModel -> m CreativeOptimizationConfigurationOptimizationModel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeOptimizationConfigurationOptimizationModel -> m CreativeOptimizationConfigurationOptimizationModel #

Ord CreativeOptimizationConfigurationOptimizationModel Source # 
Read CreativeOptimizationConfigurationOptimizationModel Source # 
Show CreativeOptimizationConfigurationOptimizationModel Source # 
Generic CreativeOptimizationConfigurationOptimizationModel Source # 
Hashable CreativeOptimizationConfigurationOptimizationModel Source # 
ToJSON CreativeOptimizationConfigurationOptimizationModel Source # 
FromJSON CreativeOptimizationConfigurationOptimizationModel Source # 
FromHttpApiData CreativeOptimizationConfigurationOptimizationModel Source # 
ToHttpApiData CreativeOptimizationConfigurationOptimizationModel Source # 
type Rep CreativeOptimizationConfigurationOptimizationModel Source # 
type Rep CreativeOptimizationConfigurationOptimizationModel = D1 (MetaData "CreativeOptimizationConfigurationOptimizationModel" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "Click" PrefixI False) U1) (C1 (MetaCons "PostClick" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PostClickAndImpression" PrefixI False) U1) ((:+:) (C1 (MetaCons "PostImpression" PrefixI False) U1) (C1 (MetaCons "VideoCompletion" PrefixI False) U1))))

AccountPermissionLevel

data AccountPermissionLevel Source #

Administrative level required to enable this account permission.

Constructors

Administrator
ADMINISTRATOR
User
USER

Instances

Enum AccountPermissionLevel Source # 
Eq AccountPermissionLevel Source # 
Data AccountPermissionLevel Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountPermissionLevel -> c AccountPermissionLevel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountPermissionLevel #

toConstr :: AccountPermissionLevel -> Constr #

dataTypeOf :: AccountPermissionLevel -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountPermissionLevel) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountPermissionLevel) #

gmapT :: (forall b. Data b => b -> b) -> AccountPermissionLevel -> AccountPermissionLevel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountPermissionLevel -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountPermissionLevel -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountPermissionLevel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountPermissionLevel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountPermissionLevel -> m AccountPermissionLevel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountPermissionLevel -> m AccountPermissionLevel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountPermissionLevel -> m AccountPermissionLevel #

Ord AccountPermissionLevel Source # 
Read AccountPermissionLevel Source # 
Show AccountPermissionLevel Source # 
Generic AccountPermissionLevel Source # 
Hashable AccountPermissionLevel Source # 
ToJSON AccountPermissionLevel Source # 
FromJSON AccountPermissionLevel Source # 
FromHttpApiData AccountPermissionLevel Source # 
ToHttpApiData AccountPermissionLevel Source # 
type Rep AccountPermissionLevel Source # 
type Rep AccountPermissionLevel = D1 (MetaData "AccountPermissionLevel" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Administrator" PrefixI False) U1) (C1 (MetaCons "User" PrefixI False) U1))

OffSetPosition

data OffSetPosition Source #

Offset Position.

See: offSetPosition smart constructor.

Instances

Eq OffSetPosition Source # 
Data OffSetPosition Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OffSetPosition -> c OffSetPosition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OffSetPosition #

toConstr :: OffSetPosition -> Constr #

dataTypeOf :: OffSetPosition -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OffSetPosition) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OffSetPosition) #

gmapT :: (forall b. Data b => b -> b) -> OffSetPosition -> OffSetPosition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OffSetPosition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OffSetPosition -> r #

gmapQ :: (forall d. Data d => d -> u) -> OffSetPosition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OffSetPosition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OffSetPosition -> m OffSetPosition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OffSetPosition -> m OffSetPosition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OffSetPosition -> m OffSetPosition #

Show OffSetPosition Source # 
Generic OffSetPosition Source # 

Associated Types

type Rep OffSetPosition :: * -> * #

ToJSON OffSetPosition Source # 
FromJSON OffSetPosition Source # 
type Rep OffSetPosition Source # 
type Rep OffSetPosition = D1 (MetaData "OffSetPosition" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "OffSetPosition'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ospLeft") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_ospTop") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

offSetPosition :: OffSetPosition Source #

Creates a value of OffSetPosition with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ospLeft :: Lens' OffSetPosition (Maybe Int32) Source #

Offset distance from left side of an asset or a window.

ospTop :: Lens' OffSetPosition (Maybe Int32) Source #

Offset distance from top side of an asset or a window.

Metric

data Metric Source #

Represents a metric.

See: metric smart constructor.

Instances

Eq Metric Source # 

Methods

(==) :: Metric -> Metric -> Bool #

(/=) :: Metric -> Metric -> Bool #

Data Metric Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Metric -> c Metric #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Metric #

toConstr :: Metric -> Constr #

dataTypeOf :: Metric -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Metric) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Metric) #

gmapT :: (forall b. Data b => b -> b) -> Metric -> Metric #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Metric -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Metric -> r #

gmapQ :: (forall d. Data d => d -> u) -> Metric -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Metric -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Metric -> m Metric #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Metric -> m Metric #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Metric -> m Metric #

Show Metric Source # 
Generic Metric Source # 

Associated Types

type Rep Metric :: * -> * #

Methods

from :: Metric -> Rep Metric x #

to :: Rep Metric x -> Metric #

ToJSON Metric Source # 
FromJSON Metric Source # 
type Rep Metric Source # 
type Rep Metric = D1 (MetaData "Metric" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Metric'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_mKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_mName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

metric :: Metric Source #

Creates a value of Metric with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

mKind :: Lens' Metric Text Source #

The kind of resource this is, in this case dfareporting#metric.

mName :: Lens' Metric (Maybe Text) Source #

The metric name, e.g. dfa:impressions

RemarketingListShare

data RemarketingListShare Source #

Contains properties of a remarketing list's sharing information. Sharing allows other accounts or advertisers to target to your remarketing lists. This resource can be used to manage remarketing list sharing to other accounts and advertisers.

See: remarketingListShare smart constructor.

Instances

Eq RemarketingListShare Source # 
Data RemarketingListShare Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RemarketingListShare -> c RemarketingListShare #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RemarketingListShare #

toConstr :: RemarketingListShare -> Constr #

dataTypeOf :: RemarketingListShare -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RemarketingListShare) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RemarketingListShare) #

gmapT :: (forall b. Data b => b -> b) -> RemarketingListShare -> RemarketingListShare #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RemarketingListShare -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RemarketingListShare -> r #

gmapQ :: (forall d. Data d => d -> u) -> RemarketingListShare -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RemarketingListShare -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RemarketingListShare -> m RemarketingListShare #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RemarketingListShare -> m RemarketingListShare #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RemarketingListShare -> m RemarketingListShare #

Show RemarketingListShare Source # 
Generic RemarketingListShare Source # 
ToJSON RemarketingListShare Source # 
FromJSON RemarketingListShare Source # 
type Rep RemarketingListShare Source # 
type Rep RemarketingListShare = D1 (MetaData "RemarketingListShare" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "RemarketingListShare'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rlsSharedAdvertiserIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64]))) (S1 (MetaSel (Just Symbol "_rlsKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rlsRemarketingListId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_rlsSharedAccountIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64]))))))

remarketingListShare :: RemarketingListShare Source #

Creates a value of RemarketingListShare with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rlsSharedAdvertiserIds :: Lens' RemarketingListShare [Int64] Source #

Advertisers that the remarketing list is shared with.

rlsKind :: Lens' RemarketingListShare Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#remarketingListShare".

rlsRemarketingListId :: Lens' RemarketingListShare (Maybe Int64) Source #

Remarketing list ID. This is a read-only, auto-generated field.

rlsSharedAccountIds :: Lens' RemarketingListShare [Int64] Source #

Accounts that the remarketing list is shared with.

EventTagsListResponse

data EventTagsListResponse Source #

Event Tag List Response

See: eventTagsListResponse smart constructor.

Instances

Eq EventTagsListResponse Source # 
Data EventTagsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventTagsListResponse -> c EventTagsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventTagsListResponse #

toConstr :: EventTagsListResponse -> Constr #

dataTypeOf :: EventTagsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EventTagsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventTagsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> EventTagsListResponse -> EventTagsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventTagsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventTagsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventTagsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventTagsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventTagsListResponse -> m EventTagsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTagsListResponse -> m EventTagsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTagsListResponse -> m EventTagsListResponse #

Show EventTagsListResponse Source # 
Generic EventTagsListResponse Source # 
ToJSON EventTagsListResponse Source # 
FromJSON EventTagsListResponse Source # 
type Rep EventTagsListResponse Source # 
type Rep EventTagsListResponse = D1 (MetaData "EventTagsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "EventTagsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_etlrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_etlrEventTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [EventTag])))))

eventTagsListResponse :: EventTagsListResponse Source #

Creates a value of EventTagsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

etlrKind :: Lens' EventTagsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#eventTagsListResponse".

UserRolesListResponse

data UserRolesListResponse Source #

User Role List Response

See: userRolesListResponse smart constructor.

Instances

Eq UserRolesListResponse Source # 
Data UserRolesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserRolesListResponse -> c UserRolesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserRolesListResponse #

toConstr :: UserRolesListResponse -> Constr #

dataTypeOf :: UserRolesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserRolesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserRolesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> UserRolesListResponse -> UserRolesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserRolesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserRolesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserRolesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserRolesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserRolesListResponse -> m UserRolesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRolesListResponse -> m UserRolesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRolesListResponse -> m UserRolesListResponse #

Show UserRolesListResponse Source # 
Generic UserRolesListResponse Source # 
ToJSON UserRolesListResponse Source # 
FromJSON UserRolesListResponse Source # 
type Rep UserRolesListResponse Source # 
type Rep UserRolesListResponse = D1 (MetaData "UserRolesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "UserRolesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_urlrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_urlrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_urlrUserRoles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UserRole]))))))

userRolesListResponse :: UserRolesListResponse Source #

Creates a value of UserRolesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

urlrNextPageToken :: Lens' UserRolesListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

urlrKind :: Lens' UserRolesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#userRolesListResponse".

ListPopulationTermType

data ListPopulationTermType Source #

List population term type determines the applicable fields in this object. If left unset or set to CUSTOM_VARIABLE_TERM, then variableName, variableFriendlyName, operator, value, and negation are applicable. If set to LIST_MEMBERSHIP_TERM then remarketingListId and contains are applicable. If set to REFERRER_TERM then operator, value, and negation are applicable.

Constructors

CustomVariableTerm
CUSTOM_VARIABLE_TERM
ListMembershipTerm
LIST_MEMBERSHIP_TERM
ReferrerTerm
REFERRER_TERM

Instances

Enum ListPopulationTermType Source # 
Eq ListPopulationTermType Source # 
Data ListPopulationTermType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListPopulationTermType -> c ListPopulationTermType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListPopulationTermType #

toConstr :: ListPopulationTermType -> Constr #

dataTypeOf :: ListPopulationTermType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ListPopulationTermType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListPopulationTermType) #

gmapT :: (forall b. Data b => b -> b) -> ListPopulationTermType -> ListPopulationTermType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListPopulationTermType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListPopulationTermType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ListPopulationTermType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ListPopulationTermType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ListPopulationTermType -> m ListPopulationTermType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ListPopulationTermType -> m ListPopulationTermType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListPopulationTermType -> m ListPopulationTermType #

Ord ListPopulationTermType Source # 
Read ListPopulationTermType Source # 
Show ListPopulationTermType Source # 
Generic ListPopulationTermType Source # 
Hashable ListPopulationTermType Source # 
ToJSON ListPopulationTermType Source # 
FromJSON ListPopulationTermType Source # 
FromHttpApiData ListPopulationTermType Source # 
ToHttpApiData ListPopulationTermType Source # 
type Rep ListPopulationTermType Source # 
type Rep ListPopulationTermType = D1 (MetaData "ListPopulationTermType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CustomVariableTerm" PrefixI False) U1) ((:+:) (C1 (MetaCons "ListMembershipTerm" PrefixI False) U1) (C1 (MetaCons "ReferrerTerm" PrefixI False) U1)))

AdvertiserGroupsListSortOrder

data AdvertiserGroupsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

AGLSOAscending
ASCENDING
AGLSODescending
DESCENDING

Instances

Enum AdvertiserGroupsListSortOrder Source # 
Eq AdvertiserGroupsListSortOrder Source # 
Data AdvertiserGroupsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdvertiserGroupsListSortOrder -> c AdvertiserGroupsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdvertiserGroupsListSortOrder #

toConstr :: AdvertiserGroupsListSortOrder -> Constr #

dataTypeOf :: AdvertiserGroupsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdvertiserGroupsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdvertiserGroupsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> AdvertiserGroupsListSortOrder -> AdvertiserGroupsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdvertiserGroupsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdvertiserGroupsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdvertiserGroupsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdvertiserGroupsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdvertiserGroupsListSortOrder -> m AdvertiserGroupsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertiserGroupsListSortOrder -> m AdvertiserGroupsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertiserGroupsListSortOrder -> m AdvertiserGroupsListSortOrder #

Ord AdvertiserGroupsListSortOrder Source # 
Read AdvertiserGroupsListSortOrder Source # 
Show AdvertiserGroupsListSortOrder Source # 
Generic AdvertiserGroupsListSortOrder Source # 
Hashable AdvertiserGroupsListSortOrder Source # 
ToJSON AdvertiserGroupsListSortOrder Source # 
FromJSON AdvertiserGroupsListSortOrder Source # 
FromHttpApiData AdvertiserGroupsListSortOrder Source # 
ToHttpApiData AdvertiserGroupsListSortOrder Source # 
type Rep AdvertiserGroupsListSortOrder Source # 
type Rep AdvertiserGroupsListSortOrder = D1 (MetaData "AdvertiserGroupsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "AGLSOAscending" PrefixI False) U1) (C1 (MetaCons "AGLSODescending" PrefixI False) U1))

CreativeFieldValuesListSortOrder

data CreativeFieldValuesListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

CFVLSOAscending
ASCENDING
CFVLSODescending
DESCENDING

Instances

Enum CreativeFieldValuesListSortOrder Source # 
Eq CreativeFieldValuesListSortOrder Source # 
Data CreativeFieldValuesListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeFieldValuesListSortOrder -> c CreativeFieldValuesListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeFieldValuesListSortOrder #

toConstr :: CreativeFieldValuesListSortOrder -> Constr #

dataTypeOf :: CreativeFieldValuesListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeFieldValuesListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeFieldValuesListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> CreativeFieldValuesListSortOrder -> CreativeFieldValuesListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeFieldValuesListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeFieldValuesListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeFieldValuesListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeFieldValuesListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeFieldValuesListSortOrder -> m CreativeFieldValuesListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeFieldValuesListSortOrder -> m CreativeFieldValuesListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeFieldValuesListSortOrder -> m CreativeFieldValuesListSortOrder #

Ord CreativeFieldValuesListSortOrder Source # 
Read CreativeFieldValuesListSortOrder Source # 
Show CreativeFieldValuesListSortOrder Source # 
Generic CreativeFieldValuesListSortOrder Source # 
Hashable CreativeFieldValuesListSortOrder Source # 
ToJSON CreativeFieldValuesListSortOrder Source # 
FromJSON CreativeFieldValuesListSortOrder Source # 
FromHttpApiData CreativeFieldValuesListSortOrder Source # 
ToHttpApiData CreativeFieldValuesListSortOrder Source # 
type Rep CreativeFieldValuesListSortOrder Source # 
type Rep CreativeFieldValuesListSortOrder = D1 (MetaData "CreativeFieldValuesListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CFVLSOAscending" PrefixI False) U1) (C1 (MetaCons "CFVLSODescending" PrefixI False) U1))

SortedDimensionSortOrder

data SortedDimensionSortOrder Source #

An optional sort order for the dimension column.

Constructors

SDSOAscending
ASCENDING
SDSODescending
DESCENDING

Instances

Enum SortedDimensionSortOrder Source # 
Eq SortedDimensionSortOrder Source # 
Data SortedDimensionSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SortedDimensionSortOrder -> c SortedDimensionSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SortedDimensionSortOrder #

toConstr :: SortedDimensionSortOrder -> Constr #

dataTypeOf :: SortedDimensionSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SortedDimensionSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortedDimensionSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> SortedDimensionSortOrder -> SortedDimensionSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortedDimensionSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortedDimensionSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> SortedDimensionSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SortedDimensionSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SortedDimensionSortOrder -> m SortedDimensionSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SortedDimensionSortOrder -> m SortedDimensionSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SortedDimensionSortOrder -> m SortedDimensionSortOrder #

Ord SortedDimensionSortOrder Source # 
Read SortedDimensionSortOrder Source # 
Show SortedDimensionSortOrder Source # 
Generic SortedDimensionSortOrder Source # 
Hashable SortedDimensionSortOrder Source # 
ToJSON SortedDimensionSortOrder Source # 
FromJSON SortedDimensionSortOrder Source # 
FromHttpApiData SortedDimensionSortOrder Source # 
ToHttpApiData SortedDimensionSortOrder Source # 
type Rep SortedDimensionSortOrder Source # 
type Rep SortedDimensionSortOrder = D1 (MetaData "SortedDimensionSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "SDSOAscending" PrefixI False) U1) (C1 (MetaCons "SDSODescending" PrefixI False) U1))

CompatibleFields

data CompatibleFields Source #

Represents a response to the queryCompatibleFields method.

See: compatibleFields smart constructor.

Instances

Eq CompatibleFields Source # 
Data CompatibleFields Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompatibleFields -> c CompatibleFields #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompatibleFields #

toConstr :: CompatibleFields -> Constr #

dataTypeOf :: CompatibleFields -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CompatibleFields) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompatibleFields) #

gmapT :: (forall b. Data b => b -> b) -> CompatibleFields -> CompatibleFields #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompatibleFields -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompatibleFields -> r #

gmapQ :: (forall d. Data d => d -> u) -> CompatibleFields -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompatibleFields -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompatibleFields -> m CompatibleFields #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompatibleFields -> m CompatibleFields #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompatibleFields -> m CompatibleFields #

Show CompatibleFields Source # 
Generic CompatibleFields Source # 
ToJSON CompatibleFields Source # 
FromJSON CompatibleFields Source # 
type Rep CompatibleFields Source # 
type Rep CompatibleFields = D1 (MetaData "CompatibleFields" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CompatibleFields'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cfReachReportCompatibleFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReachReportCompatibleFields))) ((:*:) (S1 (MetaSel (Just Symbol "_cfCrossDimensionReachReportCompatibleFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CrossDimensionReachReportCompatibleFields))) (S1 (MetaSel (Just Symbol "_cfKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cfFloodlightReportCompatibleFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FloodlightReportCompatibleFields))) ((:*:) (S1 (MetaSel (Just Symbol "_cfReportCompatibleFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportCompatibleFields))) (S1 (MetaSel (Just Symbol "_cfPathToConversionReportCompatibleFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PathToConversionReportCompatibleFields)))))))

cfReachReportCompatibleFields :: Lens' CompatibleFields (Maybe ReachReportCompatibleFields) Source #

Contains items that are compatible to be selected for a report of type "REACH".

cfCrossDimensionReachReportCompatibleFields :: Lens' CompatibleFields (Maybe CrossDimensionReachReportCompatibleFields) Source #

Contains items that are compatible to be selected for a report of type "CROSS_DIMENSION_REACH".

cfKind :: Lens' CompatibleFields Text Source #

The kind of resource this is, in this case dfareporting#compatibleFields.

cfFloodlightReportCompatibleFields :: Lens' CompatibleFields (Maybe FloodlightReportCompatibleFields) Source #

Contains items that are compatible to be selected for a report of type "FLOODLIGHT".

cfReportCompatibleFields :: Lens' CompatibleFields (Maybe ReportCompatibleFields) Source #

Contains items that are compatible to be selected for a report of type "STANDARD".

cfPathToConversionReportCompatibleFields :: Lens' CompatibleFields (Maybe PathToConversionReportCompatibleFields) Source #

Contains items that are compatible to be selected for a report of type "PATH_TO_CONVERSION".

AudienceSegment

data AudienceSegment Source #

Audience Segment.

See: audienceSegment smart constructor.

Instances

Eq AudienceSegment Source # 
Data AudienceSegment Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AudienceSegment -> c AudienceSegment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AudienceSegment #

toConstr :: AudienceSegment -> Constr #

dataTypeOf :: AudienceSegment -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AudienceSegment) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AudienceSegment) #

gmapT :: (forall b. Data b => b -> b) -> AudienceSegment -> AudienceSegment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AudienceSegment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AudienceSegment -> r #

gmapQ :: (forall d. Data d => d -> u) -> AudienceSegment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AudienceSegment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AudienceSegment -> m AudienceSegment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AudienceSegment -> m AudienceSegment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AudienceSegment -> m AudienceSegment #

Show AudienceSegment Source # 
Generic AudienceSegment Source # 
ToJSON AudienceSegment Source # 
FromJSON AudienceSegment Source # 
type Rep AudienceSegment Source # 
type Rep AudienceSegment = D1 (MetaData "AudienceSegment" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AudienceSegment'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_asName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_asId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_asAllocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))))

audienceSegment :: AudienceSegment Source #

Creates a value of AudienceSegment with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

asName :: Lens' AudienceSegment (Maybe Text) Source #

Name of this audience segment. This is a required field and must be less than 65 characters long.

asId :: Lens' AudienceSegment (Maybe Int64) Source #

ID of this audience segment. This is a read-only, auto-generated field.

asAllocation :: Lens' AudienceSegment (Maybe Int32) Source #

Weight allocated to this segment. Must be between 1 and 1000. The weight assigned will be understood in proportion to the weights assigned to other segments in the same segment group.

FilesListSortField

data FilesListSortField Source #

The field by which to sort the list.

Constructors

FLSFID

ID Sort by file ID.

FLSFLastModifiedTime

LAST_MODIFIED_TIME Sort by 'lastmodifiedAt' field.

Instances

Enum FilesListSortField Source # 
Eq FilesListSortField Source # 
Data FilesListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FilesListSortField -> c FilesListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FilesListSortField #

toConstr :: FilesListSortField -> Constr #

dataTypeOf :: FilesListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FilesListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilesListSortField) #

gmapT :: (forall b. Data b => b -> b) -> FilesListSortField -> FilesListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FilesListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FilesListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> FilesListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FilesListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FilesListSortField -> m FilesListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FilesListSortField -> m FilesListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FilesListSortField -> m FilesListSortField #

Ord FilesListSortField Source # 
Read FilesListSortField Source # 
Show FilesListSortField Source # 
Generic FilesListSortField Source # 
Hashable FilesListSortField Source # 
ToJSON FilesListSortField Source # 
FromJSON FilesListSortField Source # 
FromHttpApiData FilesListSortField Source # 
ToHttpApiData FilesListSortField Source # 
type Rep FilesListSortField Source # 
type Rep FilesListSortField = D1 (MetaData "FilesListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "FLSFID" PrefixI False) U1) (C1 (MetaCons "FLSFLastModifiedTime" PrefixI False) U1))

DirectorySiteInterstitialTagFormatsItem

data DirectorySiteInterstitialTagFormatsItem Source #

Constructors

IframeJavascriptInterstitial
IFRAME_JAVASCRIPT_INTERSTITIAL
InternalRedirectInterstitial
INTERNAL_REDIRECT_INTERSTITIAL
JavascriptInterstitial
JAVASCRIPT_INTERSTITIAL

Instances

Enum DirectorySiteInterstitialTagFormatsItem Source # 
Eq DirectorySiteInterstitialTagFormatsItem Source # 
Data DirectorySiteInterstitialTagFormatsItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectorySiteInterstitialTagFormatsItem -> c DirectorySiteInterstitialTagFormatsItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectorySiteInterstitialTagFormatsItem #

toConstr :: DirectorySiteInterstitialTagFormatsItem -> Constr #

dataTypeOf :: DirectorySiteInterstitialTagFormatsItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectorySiteInterstitialTagFormatsItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectorySiteInterstitialTagFormatsItem) #

gmapT :: (forall b. Data b => b -> b) -> DirectorySiteInterstitialTagFormatsItem -> DirectorySiteInterstitialTagFormatsItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteInterstitialTagFormatsItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteInterstitialTagFormatsItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectorySiteInterstitialTagFormatsItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectorySiteInterstitialTagFormatsItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectorySiteInterstitialTagFormatsItem -> m DirectorySiteInterstitialTagFormatsItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteInterstitialTagFormatsItem -> m DirectorySiteInterstitialTagFormatsItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteInterstitialTagFormatsItem -> m DirectorySiteInterstitialTagFormatsItem #

Ord DirectorySiteInterstitialTagFormatsItem Source # 
Read DirectorySiteInterstitialTagFormatsItem Source # 
Show DirectorySiteInterstitialTagFormatsItem Source # 
Generic DirectorySiteInterstitialTagFormatsItem Source # 
Hashable DirectorySiteInterstitialTagFormatsItem Source # 
ToJSON DirectorySiteInterstitialTagFormatsItem Source # 
FromJSON DirectorySiteInterstitialTagFormatsItem Source # 
FromHttpApiData DirectorySiteInterstitialTagFormatsItem Source # 
ToHttpApiData DirectorySiteInterstitialTagFormatsItem Source # 
type Rep DirectorySiteInterstitialTagFormatsItem Source # 
type Rep DirectorySiteInterstitialTagFormatsItem = D1 (MetaData "DirectorySiteInterstitialTagFormatsItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "IframeJavascriptInterstitial" PrefixI False) U1) ((:+:) (C1 (MetaCons "InternalRedirectInterstitial" PrefixI False) U1) (C1 (MetaCons "JavascriptInterstitial" PrefixI False) U1)))

DfpSettings

data DfpSettings Source #

DFP Settings

See: dfpSettings smart constructor.

Instances

Eq DfpSettings Source # 
Data DfpSettings Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DfpSettings -> c DfpSettings #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DfpSettings #

toConstr :: DfpSettings -> Constr #

dataTypeOf :: DfpSettings -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DfpSettings) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DfpSettings) #

gmapT :: (forall b. Data b => b -> b) -> DfpSettings -> DfpSettings #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DfpSettings -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DfpSettings -> r #

gmapQ :: (forall d. Data d => d -> u) -> DfpSettings -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DfpSettings -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DfpSettings -> m DfpSettings #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DfpSettings -> m DfpSettings #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DfpSettings -> m DfpSettings #

Show DfpSettings Source # 
Generic DfpSettings Source # 

Associated Types

type Rep DfpSettings :: * -> * #

ToJSON DfpSettings Source # 
FromJSON DfpSettings Source # 
type Rep DfpSettings Source # 
type Rep DfpSettings = D1 (MetaData "DfpSettings" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DfpSettings'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dsPubPaidPlacementAccepted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_dsDfpNetworkName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_dsPublisherPortalOnly") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_dsProgrammaticPlacementAccepted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_dsDfpNetworkCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

dfpSettings :: DfpSettings Source #

Creates a value of DfpSettings with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dsPubPaidPlacementAccepted :: Lens' DfpSettings (Maybe Bool) Source #

Whether this directory site accepts publisher-paid tags.

dsDfpNetworkName :: Lens' DfpSettings (Maybe Text) Source #

DFP network name for this directory site.

dsPublisherPortalOnly :: Lens' DfpSettings (Maybe Bool) Source #

Whether this directory site is available only via DoubleClick Publisher Portal.

dsProgrammaticPlacementAccepted :: Lens' DfpSettings (Maybe Bool) Source #

Whether this directory site accepts programmatic placements.

dsDfpNetworkCode :: Lens' DfpSettings (Maybe Text) Source #

DFP network code for this directory site.

EventTagsListSortField

data EventTagsListSortField Source #

Field by which to sort the list.

Constructors

ETLSFID
ID
ETLSFName
NAME

Instances

Enum EventTagsListSortField Source # 
Eq EventTagsListSortField Source # 
Data EventTagsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventTagsListSortField -> c EventTagsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventTagsListSortField #

toConstr :: EventTagsListSortField -> Constr #

dataTypeOf :: EventTagsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EventTagsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventTagsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> EventTagsListSortField -> EventTagsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventTagsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventTagsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventTagsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventTagsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventTagsListSortField -> m EventTagsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTagsListSortField -> m EventTagsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTagsListSortField -> m EventTagsListSortField #

Ord EventTagsListSortField Source # 
Read EventTagsListSortField Source # 
Show EventTagsListSortField Source # 
Generic EventTagsListSortField Source # 
Hashable EventTagsListSortField Source # 
ToJSON EventTagsListSortField Source # 
FromJSON EventTagsListSortField Source # 
FromHttpApiData EventTagsListSortField Source # 
ToHttpApiData EventTagsListSortField Source # 
type Rep EventTagsListSortField Source # 
type Rep EventTagsListSortField = D1 (MetaData "EventTagsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ETLSFID" PrefixI False) U1) (C1 (MetaCons "ETLSFName" PrefixI False) U1))

PathToConversionReportCompatibleFields

data PathToConversionReportCompatibleFields Source #

Represents fields that are compatible to be selected for a report of type "PATH_TO_CONVERSION".

See: pathToConversionReportCompatibleFields smart constructor.

Instances

Eq PathToConversionReportCompatibleFields Source # 
Data PathToConversionReportCompatibleFields Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PathToConversionReportCompatibleFields -> c PathToConversionReportCompatibleFields #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PathToConversionReportCompatibleFields #

toConstr :: PathToConversionReportCompatibleFields -> Constr #

dataTypeOf :: PathToConversionReportCompatibleFields -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PathToConversionReportCompatibleFields) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PathToConversionReportCompatibleFields) #

gmapT :: (forall b. Data b => b -> b) -> PathToConversionReportCompatibleFields -> PathToConversionReportCompatibleFields #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PathToConversionReportCompatibleFields -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PathToConversionReportCompatibleFields -> r #

gmapQ :: (forall d. Data d => d -> u) -> PathToConversionReportCompatibleFields -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PathToConversionReportCompatibleFields -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PathToConversionReportCompatibleFields -> m PathToConversionReportCompatibleFields #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PathToConversionReportCompatibleFields -> m PathToConversionReportCompatibleFields #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PathToConversionReportCompatibleFields -> m PathToConversionReportCompatibleFields #

Show PathToConversionReportCompatibleFields Source # 
Generic PathToConversionReportCompatibleFields Source # 
ToJSON PathToConversionReportCompatibleFields Source # 
FromJSON PathToConversionReportCompatibleFields Source # 
type Rep PathToConversionReportCompatibleFields Source # 
type Rep PathToConversionReportCompatibleFields = D1 (MetaData "PathToConversionReportCompatibleFields" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PathToConversionReportCompatibleFields'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ptcrcfMetrics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Metric]))) (S1 (MetaSel (Just Symbol "_ptcrcfKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ptcrcfConversionDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension]))) ((:*:) (S1 (MetaSel (Just Symbol "_ptcrcfCustomFloodlightVariables") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension]))) (S1 (MetaSel (Just Symbol "_ptcrcfPerInteractionDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension])))))))

ptcrcfMetrics :: Lens' PathToConversionReportCompatibleFields [Metric] Source #

Metrics which are compatible to be selected in the "metricNames" section of the report.

ptcrcfKind :: Lens' PathToConversionReportCompatibleFields Text Source #

The kind of resource this is, in this case dfareporting#pathToConversionReportCompatibleFields.

ptcrcfConversionDimensions :: Lens' PathToConversionReportCompatibleFields [Dimension] Source #

Conversion dimensions which are compatible to be selected in the "conversionDimensions" section of the report.

ptcrcfCustomFloodlightVariables :: Lens' PathToConversionReportCompatibleFields [Dimension] Source #

Custom floodlight variables which are compatible to be selected in the "customFloodlightVariables" section of the report.

ptcrcfPerInteractionDimensions :: Lens' PathToConversionReportCompatibleFields [Dimension] Source #

Per-interaction dimensions which are compatible to be selected in the "perInteractionDimensions" section of the report.

InventoryItemType

data InventoryItemType Source #

Type of inventory item.

Constructors

IITPlanningPlacementTypeCredit
PLANNING_PLACEMENT_TYPE_CREDIT
IITPlanningPlacementTypeRegular
PLANNING_PLACEMENT_TYPE_REGULAR

Instances

Enum InventoryItemType Source # 
Eq InventoryItemType Source # 
Data InventoryItemType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InventoryItemType -> c InventoryItemType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InventoryItemType #

toConstr :: InventoryItemType -> Constr #

dataTypeOf :: InventoryItemType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InventoryItemType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InventoryItemType) #

gmapT :: (forall b. Data b => b -> b) -> InventoryItemType -> InventoryItemType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InventoryItemType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InventoryItemType -> r #

gmapQ :: (forall d. Data d => d -> u) -> InventoryItemType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InventoryItemType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InventoryItemType -> m InventoryItemType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryItemType -> m InventoryItemType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryItemType -> m InventoryItemType #

Ord InventoryItemType Source # 
Read InventoryItemType Source # 
Show InventoryItemType Source # 
Generic InventoryItemType Source # 
Hashable InventoryItemType Source # 
ToJSON InventoryItemType Source # 
FromJSON InventoryItemType Source # 
FromHttpApiData InventoryItemType Source # 
ToHttpApiData InventoryItemType Source # 
type Rep InventoryItemType Source # 
type Rep InventoryItemType = D1 (MetaData "InventoryItemType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "IITPlanningPlacementTypeCredit" PrefixI False) U1) (C1 (MetaCons "IITPlanningPlacementTypeRegular" PrefixI False) U1))

CreativeAssetPositionTopUnit

data CreativeAssetPositionTopUnit Source #

Offset top unit for an asset. This is a read-only field if the asset displayType is ASSET_DISPLAY_TYPE_OVERLAY. Applicable to the following creative types: all RICH_MEDIA.

Constructors

CAPTUOffSetUnitPercent
OFFSET_UNIT_PERCENT
CAPTUOffSetUnitPixel
OFFSET_UNIT_PIXEL
CAPTUOffSetUnitPixelFromCenter
OFFSET_UNIT_PIXEL_FROM_CENTER

Instances

Enum CreativeAssetPositionTopUnit Source # 
Eq CreativeAssetPositionTopUnit Source # 
Data CreativeAssetPositionTopUnit Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetPositionTopUnit -> c CreativeAssetPositionTopUnit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetPositionTopUnit #

toConstr :: CreativeAssetPositionTopUnit -> Constr #

dataTypeOf :: CreativeAssetPositionTopUnit -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetPositionTopUnit) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetPositionTopUnit) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetPositionTopUnit -> CreativeAssetPositionTopUnit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetPositionTopUnit -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetPositionTopUnit -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetPositionTopUnit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetPositionTopUnit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetPositionTopUnit -> m CreativeAssetPositionTopUnit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetPositionTopUnit -> m CreativeAssetPositionTopUnit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetPositionTopUnit -> m CreativeAssetPositionTopUnit #

Ord CreativeAssetPositionTopUnit Source # 
Read CreativeAssetPositionTopUnit Source # 
Show CreativeAssetPositionTopUnit Source # 
Generic CreativeAssetPositionTopUnit Source # 
Hashable CreativeAssetPositionTopUnit Source # 
ToJSON CreativeAssetPositionTopUnit Source # 
FromJSON CreativeAssetPositionTopUnit Source # 
FromHttpApiData CreativeAssetPositionTopUnit Source # 
ToHttpApiData CreativeAssetPositionTopUnit Source # 
type Rep CreativeAssetPositionTopUnit Source # 
type Rep CreativeAssetPositionTopUnit = D1 (MetaData "CreativeAssetPositionTopUnit" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CAPTUOffSetUnitPercent" PrefixI False) U1) ((:+:) (C1 (MetaCons "CAPTUOffSetUnitPixel" PrefixI False) U1) (C1 (MetaCons "CAPTUOffSetUnitPixelFromCenter" PrefixI False) U1)))

City

data City Source #

Contains information about a city that can be targeted by ads.

See: city smart constructor.

Instances

Eq City Source # 

Methods

(==) :: City -> City -> Bool #

(/=) :: City -> City -> Bool #

Data City Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> City -> c City #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c City #

toConstr :: City -> Constr #

dataTypeOf :: City -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c City) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c City) #

gmapT :: (forall b. Data b => b -> b) -> City -> City #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> City -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> City -> r #

gmapQ :: (forall d. Data d => d -> u) -> City -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> City -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> City -> m City #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> City -> m City #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> City -> m City #

Show City Source # 

Methods

showsPrec :: Int -> City -> ShowS #

show :: City -> String #

showList :: [City] -> ShowS #

Generic City Source # 

Associated Types

type Rep City :: * -> * #

Methods

from :: City -> Rep City x #

to :: Rep City x -> City #

ToJSON City Source # 
FromJSON City Source # 
type Rep City Source # 

city :: City Source #

Creates a value of City with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ccMetroCode :: Lens' City (Maybe Text) Source #

Metro region code of the metro region (DMA) to which this city belongs.

ccRegionCode :: Lens' City (Maybe Text) Source #

Region code of the region to which this city belongs.

ccKind :: Lens' City Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#city".

ccRegionDartId :: Lens' City (Maybe Int64) Source #

DART ID of the region to which this city belongs.

ccMetroDmaId :: Lens' City (Maybe Int64) Source #

ID of the metro region (DMA) to which this city belongs.

ccName :: Lens' City (Maybe Text) Source #

Name of this city.

ccCountryCode :: Lens' City (Maybe Text) Source #

Country code of the country to which this city belongs.

ccCountryDartId :: Lens' City (Maybe Int64) Source #

DART ID of the country to which this city belongs.

ccDartId :: Lens' City (Maybe Int64) Source #

DART ID of this city. This is the ID used for targeting and generating reports.

PlatformType

data PlatformType Source #

Contains information about a platform type that can be targeted by ads.

See: platformType smart constructor.

Instances

Eq PlatformType Source # 
Data PlatformType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlatformType -> c PlatformType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlatformType #

toConstr :: PlatformType -> Constr #

dataTypeOf :: PlatformType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlatformType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlatformType) #

gmapT :: (forall b. Data b => b -> b) -> PlatformType -> PlatformType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlatformType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlatformType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlatformType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlatformType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlatformType -> m PlatformType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlatformType -> m PlatformType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlatformType -> m PlatformType #

Show PlatformType Source # 
Generic PlatformType Source # 

Associated Types

type Rep PlatformType :: * -> * #

ToJSON PlatformType Source # 
FromJSON PlatformType Source # 
type Rep PlatformType Source # 
type Rep PlatformType = D1 (MetaData "PlatformType" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PlatformType'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ptKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_ptName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ptId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

platformType :: PlatformType Source #

Creates a value of PlatformType with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ptKind :: Lens' PlatformType Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#platformType".

ptName :: Lens' PlatformType (Maybe Text) Source #

Name of this platform type.

ptId :: Lens' PlatformType (Maybe Int64) Source #

ID of this platform type.

FloodlightActivityFloodlightActivityGroupType

data FloodlightActivityFloodlightActivityGroupType Source #

Type of the associated floodlight activity group. This is a read-only field.

Constructors

FAFAGTCounter
COUNTER
FAFAGTSale
SALE

Instances

Enum FloodlightActivityFloodlightActivityGroupType Source # 
Eq FloodlightActivityFloodlightActivityGroupType Source # 
Data FloodlightActivityFloodlightActivityGroupType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivityFloodlightActivityGroupType -> c FloodlightActivityFloodlightActivityGroupType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivityFloodlightActivityGroupType #

toConstr :: FloodlightActivityFloodlightActivityGroupType -> Constr #

dataTypeOf :: FloodlightActivityFloodlightActivityGroupType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivityFloodlightActivityGroupType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivityFloodlightActivityGroupType) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivityFloodlightActivityGroupType -> FloodlightActivityFloodlightActivityGroupType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityFloodlightActivityGroupType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityFloodlightActivityGroupType -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivityFloodlightActivityGroupType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivityFloodlightActivityGroupType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivityFloodlightActivityGroupType -> m FloodlightActivityFloodlightActivityGroupType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityFloodlightActivityGroupType -> m FloodlightActivityFloodlightActivityGroupType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityFloodlightActivityGroupType -> m FloodlightActivityFloodlightActivityGroupType #

Ord FloodlightActivityFloodlightActivityGroupType Source # 
Read FloodlightActivityFloodlightActivityGroupType Source # 
Show FloodlightActivityFloodlightActivityGroupType Source # 
Generic FloodlightActivityFloodlightActivityGroupType Source # 
Hashable FloodlightActivityFloodlightActivityGroupType Source # 
ToJSON FloodlightActivityFloodlightActivityGroupType Source # 
FromJSON FloodlightActivityFloodlightActivityGroupType Source # 
FromHttpApiData FloodlightActivityFloodlightActivityGroupType Source # 
ToHttpApiData FloodlightActivityFloodlightActivityGroupType Source # 
type Rep FloodlightActivityFloodlightActivityGroupType Source # 
type Rep FloodlightActivityFloodlightActivityGroupType = D1 (MetaData "FloodlightActivityFloodlightActivityGroupType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "FAFAGTCounter" PrefixI False) U1) (C1 (MetaCons "FAFAGTSale" PrefixI False) U1))

DirectorySiteContactsListSortOrder

data DirectorySiteContactsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

DSCLSOAscending
ASCENDING
DSCLSODescending
DESCENDING

Instances

Enum DirectorySiteContactsListSortOrder Source # 
Eq DirectorySiteContactsListSortOrder Source # 
Data DirectorySiteContactsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectorySiteContactsListSortOrder -> c DirectorySiteContactsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectorySiteContactsListSortOrder #

toConstr :: DirectorySiteContactsListSortOrder -> Constr #

dataTypeOf :: DirectorySiteContactsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectorySiteContactsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectorySiteContactsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> DirectorySiteContactsListSortOrder -> DirectorySiteContactsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteContactsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteContactsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectorySiteContactsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectorySiteContactsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectorySiteContactsListSortOrder -> m DirectorySiteContactsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteContactsListSortOrder -> m DirectorySiteContactsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteContactsListSortOrder -> m DirectorySiteContactsListSortOrder #

Ord DirectorySiteContactsListSortOrder Source # 
Read DirectorySiteContactsListSortOrder Source # 
Show DirectorySiteContactsListSortOrder Source # 
Generic DirectorySiteContactsListSortOrder Source # 
Hashable DirectorySiteContactsListSortOrder Source # 
ToJSON DirectorySiteContactsListSortOrder Source # 
FromJSON DirectorySiteContactsListSortOrder Source # 
FromHttpApiData DirectorySiteContactsListSortOrder Source # 
ToHttpApiData DirectorySiteContactsListSortOrder Source # 
type Rep DirectorySiteContactsListSortOrder Source # 
type Rep DirectorySiteContactsListSortOrder = D1 (MetaData "DirectorySiteContactsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "DSCLSOAscending" PrefixI False) U1) (C1 (MetaCons "DSCLSODescending" PrefixI False) U1))

PricingGroupType

data PricingGroupType Source #

Group type of this inventory item if it represents a placement group. Is null otherwise. There are two type of placement groups: PLANNING_PLACEMENT_GROUP_TYPE_PACKAGE is a simple group of inventory items that acts as a single pricing point for a group of tags. PLANNING_PLACEMENT_GROUP_TYPE_ROADBLOCK is a group of inventory items that not only acts as a single pricing point, but also assumes that all the tags in it will be served at the same time. A roadblock requires one of its assigned inventory items to be marked as primary.

Constructors

PlanningPlacementGroupTypePackage
PLANNING_PLACEMENT_GROUP_TYPE_PACKAGE
PlanningPlacementGroupTypeRoadblock
PLANNING_PLACEMENT_GROUP_TYPE_ROADBLOCK

Instances

Enum PricingGroupType Source # 
Eq PricingGroupType Source # 
Data PricingGroupType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PricingGroupType -> c PricingGroupType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PricingGroupType #

toConstr :: PricingGroupType -> Constr #

dataTypeOf :: PricingGroupType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PricingGroupType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PricingGroupType) #

gmapT :: (forall b. Data b => b -> b) -> PricingGroupType -> PricingGroupType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PricingGroupType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PricingGroupType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PricingGroupType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PricingGroupType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PricingGroupType -> m PricingGroupType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PricingGroupType -> m PricingGroupType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PricingGroupType -> m PricingGroupType #

Ord PricingGroupType Source # 
Read PricingGroupType Source # 
Show PricingGroupType Source # 
Generic PricingGroupType Source # 
Hashable PricingGroupType Source # 
ToJSON PricingGroupType Source # 
FromJSON PricingGroupType Source # 
FromHttpApiData PricingGroupType Source # 
ToHttpApiData PricingGroupType Source # 
type Rep PricingGroupType Source # 
type Rep PricingGroupType = D1 (MetaData "PricingGroupType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PlanningPlacementGroupTypePackage" PrefixI False) U1) (C1 (MetaCons "PlanningPlacementGroupTypeRoadblock" PrefixI False) U1))

KeyValueTargetingExpression

data KeyValueTargetingExpression Source #

Key Value Targeting Expression.

See: keyValueTargetingExpression smart constructor.

Instances

Eq KeyValueTargetingExpression Source # 
Data KeyValueTargetingExpression Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeyValueTargetingExpression -> c KeyValueTargetingExpression #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KeyValueTargetingExpression #

toConstr :: KeyValueTargetingExpression -> Constr #

dataTypeOf :: KeyValueTargetingExpression -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c KeyValueTargetingExpression) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeyValueTargetingExpression) #

gmapT :: (forall b. Data b => b -> b) -> KeyValueTargetingExpression -> KeyValueTargetingExpression #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeyValueTargetingExpression -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeyValueTargetingExpression -> r #

gmapQ :: (forall d. Data d => d -> u) -> KeyValueTargetingExpression -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KeyValueTargetingExpression -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeyValueTargetingExpression -> m KeyValueTargetingExpression #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyValueTargetingExpression -> m KeyValueTargetingExpression #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyValueTargetingExpression -> m KeyValueTargetingExpression #

Show KeyValueTargetingExpression Source # 
Generic KeyValueTargetingExpression Source # 
ToJSON KeyValueTargetingExpression Source # 
FromJSON KeyValueTargetingExpression Source # 
type Rep KeyValueTargetingExpression Source # 
type Rep KeyValueTargetingExpression = D1 (MetaData "KeyValueTargetingExpression" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" True) (C1 (MetaCons "KeyValueTargetingExpression'" PrefixI True) (S1 (MetaSel (Just Symbol "_kvteExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

keyValueTargetingExpression :: KeyValueTargetingExpression Source #

Creates a value of KeyValueTargetingExpression with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

kvteExpression :: Lens' KeyValueTargetingExpression (Maybe Text) Source #

Keyword expression being targeted by the ad.

CompanionClickThroughOverride

data CompanionClickThroughOverride Source #

Companion Click-through override.

See: companionClickThroughOverride smart constructor.

Instances

Eq CompanionClickThroughOverride Source # 
Data CompanionClickThroughOverride Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompanionClickThroughOverride -> c CompanionClickThroughOverride #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompanionClickThroughOverride #

toConstr :: CompanionClickThroughOverride -> Constr #

dataTypeOf :: CompanionClickThroughOverride -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CompanionClickThroughOverride) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompanionClickThroughOverride) #

gmapT :: (forall b. Data b => b -> b) -> CompanionClickThroughOverride -> CompanionClickThroughOverride #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompanionClickThroughOverride -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompanionClickThroughOverride -> r #

gmapQ :: (forall d. Data d => d -> u) -> CompanionClickThroughOverride -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompanionClickThroughOverride -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompanionClickThroughOverride -> m CompanionClickThroughOverride #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompanionClickThroughOverride -> m CompanionClickThroughOverride #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompanionClickThroughOverride -> m CompanionClickThroughOverride #

Show CompanionClickThroughOverride Source # 
Generic CompanionClickThroughOverride Source # 
ToJSON CompanionClickThroughOverride Source # 
FromJSON CompanionClickThroughOverride Source # 
type Rep CompanionClickThroughOverride Source # 
type Rep CompanionClickThroughOverride = D1 (MetaData "CompanionClickThroughOverride" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CompanionClickThroughOverride'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cctoCreativeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_cctoClickThroughURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ClickThroughURL)))))

companionClickThroughOverride :: CompanionClickThroughOverride Source #

Creates a value of CompanionClickThroughOverride with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cctoCreativeId :: Lens' CompanionClickThroughOverride (Maybe Int64) Source #

ID of the creative for this companion click-through override.

cctoClickThroughURL :: Lens' CompanionClickThroughOverride (Maybe ClickThroughURL) Source #

Click-through URL of this companion click-through override.

AdsListCreativeType

data AdsListCreativeType Source #

Select only ads with the specified creativeType.

Constructors

ALCTBrandSafeDefaultInstreamVideo
BRAND_SAFE_DEFAULT_INSTREAM_VIDEO
ALCTCustomDisplay
CUSTOM_DISPLAY
ALCTCustomDisplayInterstitial
CUSTOM_DISPLAY_INTERSTITIAL
ALCTDisplay
DISPLAY
ALCTDisplayImageGallery
DISPLAY_IMAGE_GALLERY
ALCTDisplayRedirect
DISPLAY_REDIRECT
ALCTFlashInpage
FLASH_INPAGE
ALCTHTML5Banner
HTML5_BANNER
ALCTImage
IMAGE
ALCTInstreamVideo
INSTREAM_VIDEO
ALCTInstreamVideoRedirect
INSTREAM_VIDEO_REDIRECT
ALCTInternalRedirect
INTERNAL_REDIRECT
ALCTInterstitialInternalRedirect
INTERSTITIAL_INTERNAL_REDIRECT
ALCTRichMediaDisplayBanner
RICH_MEDIA_DISPLAY_BANNER
ALCTRichMediaDisplayExpanding
RICH_MEDIA_DISPLAY_EXPANDING
ALCTRichMediaDisplayInterstitial
RICH_MEDIA_DISPLAY_INTERSTITIAL
ALCTRichMediaDisplayMultiFloatingInterstitial
RICH_MEDIA_DISPLAY_MULTI_FLOATING_INTERSTITIAL
ALCTRichMediaImExpand
RICH_MEDIA_IM_EXPAND
ALCTRichMediaInpageFloating
RICH_MEDIA_INPAGE_FLOATING
ALCTRichMediaMobileInApp
RICH_MEDIA_MOBILE_IN_APP
ALCTRichMediaPeelDown
RICH_MEDIA_PEEL_DOWN
ALCTTrackingText
TRACKING_TEXT
ALCTVpaidLinearVideo
VPAID_LINEAR_VIDEO
ALCTVpaidNonLinearVideo
VPAID_NON_LINEAR_VIDEO

Instances

Enum AdsListCreativeType Source # 
Eq AdsListCreativeType Source # 
Data AdsListCreativeType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdsListCreativeType -> c AdsListCreativeType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdsListCreativeType #

toConstr :: AdsListCreativeType -> Constr #

dataTypeOf :: AdsListCreativeType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdsListCreativeType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdsListCreativeType) #

gmapT :: (forall b. Data b => b -> b) -> AdsListCreativeType -> AdsListCreativeType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdsListCreativeType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdsListCreativeType -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdsListCreativeType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdsListCreativeType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdsListCreativeType -> m AdsListCreativeType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdsListCreativeType -> m AdsListCreativeType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdsListCreativeType -> m AdsListCreativeType #

Ord AdsListCreativeType Source # 
Read AdsListCreativeType Source # 
Show AdsListCreativeType Source # 
Generic AdsListCreativeType Source # 
Hashable AdsListCreativeType Source # 
ToJSON AdsListCreativeType Source # 
FromJSON AdsListCreativeType Source # 
FromHttpApiData AdsListCreativeType Source # 
ToHttpApiData AdsListCreativeType Source # 
type Rep AdsListCreativeType Source # 
type Rep AdsListCreativeType = D1 (MetaData "AdsListCreativeType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ALCTBrandSafeDefaultInstreamVideo" PrefixI False) U1) ((:+:) (C1 (MetaCons "ALCTCustomDisplay" PrefixI False) U1) (C1 (MetaCons "ALCTCustomDisplayInterstitial" PrefixI False) U1))) ((:+:) (C1 (MetaCons "ALCTDisplay" PrefixI False) U1) ((:+:) (C1 (MetaCons "ALCTDisplayImageGallery" PrefixI False) U1) (C1 (MetaCons "ALCTDisplayRedirect" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "ALCTFlashInpage" PrefixI False) U1) ((:+:) (C1 (MetaCons "ALCTHTML5Banner" PrefixI False) U1) (C1 (MetaCons "ALCTImage" PrefixI False) U1))) ((:+:) (C1 (MetaCons "ALCTInstreamVideo" PrefixI False) U1) ((:+:) (C1 (MetaCons "ALCTInstreamVideoRedirect" PrefixI False) U1) (C1 (MetaCons "ALCTInternalRedirect" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ALCTInterstitialInternalRedirect" PrefixI False) U1) ((:+:) (C1 (MetaCons "ALCTRichMediaDisplayBanner" PrefixI False) U1) (C1 (MetaCons "ALCTRichMediaDisplayExpanding" PrefixI False) U1))) ((:+:) (C1 (MetaCons "ALCTRichMediaDisplayInterstitial" PrefixI False) U1) ((:+:) (C1 (MetaCons "ALCTRichMediaDisplayMultiFloatingInterstitial" PrefixI False) U1) (C1 (MetaCons "ALCTRichMediaImExpand" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "ALCTRichMediaInpageFloating" PrefixI False) U1) ((:+:) (C1 (MetaCons "ALCTRichMediaMobileInApp" PrefixI False) U1) (C1 (MetaCons "ALCTRichMediaPeelDown" PrefixI False) U1))) ((:+:) (C1 (MetaCons "ALCTTrackingText" PrefixI False) U1) ((:+:) (C1 (MetaCons "ALCTVpaidLinearVideo" PrefixI False) U1) (C1 (MetaCons "ALCTVpaidNonLinearVideo" PrefixI False) U1))))))

FloodlightActivityGroupsListSortOrder

data FloodlightActivityGroupsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

FAGLSOAscending
ASCENDING
FAGLSODescending
DESCENDING

Instances

Enum FloodlightActivityGroupsListSortOrder Source # 
Eq FloodlightActivityGroupsListSortOrder Source # 
Data FloodlightActivityGroupsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivityGroupsListSortOrder -> c FloodlightActivityGroupsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivityGroupsListSortOrder #

toConstr :: FloodlightActivityGroupsListSortOrder -> Constr #

dataTypeOf :: FloodlightActivityGroupsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivityGroupsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivityGroupsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivityGroupsListSortOrder -> FloodlightActivityGroupsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityGroupsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityGroupsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivityGroupsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivityGroupsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupsListSortOrder -> m FloodlightActivityGroupsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupsListSortOrder -> m FloodlightActivityGroupsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupsListSortOrder -> m FloodlightActivityGroupsListSortOrder #

Ord FloodlightActivityGroupsListSortOrder Source # 
Read FloodlightActivityGroupsListSortOrder Source # 
Show FloodlightActivityGroupsListSortOrder Source # 
Generic FloodlightActivityGroupsListSortOrder Source # 
Hashable FloodlightActivityGroupsListSortOrder Source # 
ToJSON FloodlightActivityGroupsListSortOrder Source # 
FromJSON FloodlightActivityGroupsListSortOrder Source # 
FromHttpApiData FloodlightActivityGroupsListSortOrder Source # 
ToHttpApiData FloodlightActivityGroupsListSortOrder Source # 
type Rep FloodlightActivityGroupsListSortOrder Source # 
type Rep FloodlightActivityGroupsListSortOrder = D1 (MetaData "FloodlightActivityGroupsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "FAGLSOAscending" PrefixI False) U1) (C1 (MetaCons "FAGLSODescending" PrefixI False) U1))

CreativeRotationType

data CreativeRotationType Source #

Type of creative rotation. Can be used to specify whether to use sequential or random rotation.

Constructors

CreativeRotationTypeRandom
CREATIVE_ROTATION_TYPE_RANDOM
CreativeRotationTypeSequential
CREATIVE_ROTATION_TYPE_SEQUENTIAL

Instances

Enum CreativeRotationType Source # 
Eq CreativeRotationType Source # 
Data CreativeRotationType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeRotationType -> c CreativeRotationType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeRotationType #

toConstr :: CreativeRotationType -> Constr #

dataTypeOf :: CreativeRotationType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeRotationType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeRotationType) #

gmapT :: (forall b. Data b => b -> b) -> CreativeRotationType -> CreativeRotationType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeRotationType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeRotationType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeRotationType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeRotationType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeRotationType -> m CreativeRotationType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeRotationType -> m CreativeRotationType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeRotationType -> m CreativeRotationType #

Ord CreativeRotationType Source # 
Read CreativeRotationType Source # 
Show CreativeRotationType Source # 
Generic CreativeRotationType Source # 
Hashable CreativeRotationType Source # 
ToJSON CreativeRotationType Source # 
FromJSON CreativeRotationType Source # 
FromHttpApiData CreativeRotationType Source # 
ToHttpApiData CreativeRotationType Source # 
type Rep CreativeRotationType Source # 
type Rep CreativeRotationType = D1 (MetaData "CreativeRotationType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CreativeRotationTypeRandom" PrefixI False) U1) (C1 (MetaCons "CreativeRotationTypeSequential" PrefixI False) U1))

OrdersListSortField

data OrdersListSortField Source #

Field by which to sort the list.

Constructors

OLSFID
ID
OLSFName
NAME

Instances

Enum OrdersListSortField Source # 
Eq OrdersListSortField Source # 
Data OrdersListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrdersListSortField -> c OrdersListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrdersListSortField #

toConstr :: OrdersListSortField -> Constr #

dataTypeOf :: OrdersListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrdersListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrdersListSortField) #

gmapT :: (forall b. Data b => b -> b) -> OrdersListSortField -> OrdersListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrdersListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrdersListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrdersListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrdersListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrdersListSortField -> m OrdersListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrdersListSortField -> m OrdersListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrdersListSortField -> m OrdersListSortField #

Ord OrdersListSortField Source # 
Read OrdersListSortField Source # 
Show OrdersListSortField Source # 
Generic OrdersListSortField Source # 
Hashable OrdersListSortField Source # 
ToJSON OrdersListSortField Source # 
FromJSON OrdersListSortField Source # 
FromHttpApiData OrdersListSortField Source # 
ToHttpApiData OrdersListSortField Source # 
type Rep OrdersListSortField Source # 
type Rep OrdersListSortField = D1 (MetaData "OrdersListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "OLSFID" PrefixI False) U1) (C1 (MetaCons "OLSFName" PrefixI False) U1))

PlacementGroupsListSortField

data PlacementGroupsListSortField Source #

Field by which to sort the list.

Constructors

PGLSFID
ID
PGLSFName
NAME

Instances

Enum PlacementGroupsListSortField Source # 
Eq PlacementGroupsListSortField Source # 
Data PlacementGroupsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementGroupsListSortField -> c PlacementGroupsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementGroupsListSortField #

toConstr :: PlacementGroupsListSortField -> Constr #

dataTypeOf :: PlacementGroupsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementGroupsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementGroupsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> PlacementGroupsListSortField -> PlacementGroupsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroupsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroupsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementGroupsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementGroupsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementGroupsListSortField -> m PlacementGroupsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroupsListSortField -> m PlacementGroupsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroupsListSortField -> m PlacementGroupsListSortField #

Ord PlacementGroupsListSortField Source # 
Read PlacementGroupsListSortField Source # 
Show PlacementGroupsListSortField Source # 
Generic PlacementGroupsListSortField Source # 
Hashable PlacementGroupsListSortField Source # 
ToJSON PlacementGroupsListSortField Source # 
FromJSON PlacementGroupsListSortField Source # 
FromHttpApiData PlacementGroupsListSortField Source # 
ToHttpApiData PlacementGroupsListSortField Source # 
type Rep PlacementGroupsListSortField Source # 
type Rep PlacementGroupsListSortField = D1 (MetaData "PlacementGroupsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PGLSFID" PrefixI False) U1) (C1 (MetaCons "PGLSFName" PrefixI False) U1))

DirectorySitesListSortOrder

data DirectorySitesListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

DSLSOAscending
ASCENDING
DSLSODescending
DESCENDING

Instances

Enum DirectorySitesListSortOrder Source # 
Eq DirectorySitesListSortOrder Source # 
Data DirectorySitesListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectorySitesListSortOrder -> c DirectorySitesListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectorySitesListSortOrder #

toConstr :: DirectorySitesListSortOrder -> Constr #

dataTypeOf :: DirectorySitesListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectorySitesListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectorySitesListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> DirectorySitesListSortOrder -> DirectorySitesListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySitesListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySitesListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectorySitesListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectorySitesListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectorySitesListSortOrder -> m DirectorySitesListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySitesListSortOrder -> m DirectorySitesListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySitesListSortOrder -> m DirectorySitesListSortOrder #

Ord DirectorySitesListSortOrder Source # 
Read DirectorySitesListSortOrder Source # 
Show DirectorySitesListSortOrder Source # 
Generic DirectorySitesListSortOrder Source # 
Hashable DirectorySitesListSortOrder Source # 
ToJSON DirectorySitesListSortOrder Source # 
FromJSON DirectorySitesListSortOrder Source # 
FromHttpApiData DirectorySitesListSortOrder Source # 
ToHttpApiData DirectorySitesListSortOrder Source # 
type Rep DirectorySitesListSortOrder Source # 
type Rep DirectorySitesListSortOrder = D1 (MetaData "DirectorySitesListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "DSLSOAscending" PrefixI False) U1) (C1 (MetaCons "DSLSODescending" PrefixI False) U1))

AdvertisersListResponse

data AdvertisersListResponse Source #

Advertiser List Response

See: advertisersListResponse smart constructor.

Instances

Eq AdvertisersListResponse Source # 
Data AdvertisersListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdvertisersListResponse -> c AdvertisersListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdvertisersListResponse #

toConstr :: AdvertisersListResponse -> Constr #

dataTypeOf :: AdvertisersListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdvertisersListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdvertisersListResponse) #

gmapT :: (forall b. Data b => b -> b) -> AdvertisersListResponse -> AdvertisersListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdvertisersListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdvertisersListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdvertisersListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdvertisersListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdvertisersListResponse -> m AdvertisersListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertisersListResponse -> m AdvertisersListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertisersListResponse -> m AdvertisersListResponse #

Show AdvertisersListResponse Source # 
Generic AdvertisersListResponse Source # 
ToJSON AdvertisersListResponse Source # 
FromJSON AdvertisersListResponse Source # 
type Rep AdvertisersListResponse Source # 
type Rep AdvertisersListResponse = D1 (MetaData "AdvertisersListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AdvertisersListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_advNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_advKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_advAdvertisers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Advertiser]))))))

advertisersListResponse :: AdvertisersListResponse Source #

Creates a value of AdvertisersListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

advNextPageToken :: Lens' AdvertisersListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

advKind :: Lens' AdvertisersListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#advertisersListResponse".

CountriesListResponse

data CountriesListResponse Source #

Country List Response

See: countriesListResponse smart constructor.

Instances

Eq CountriesListResponse Source # 
Data CountriesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CountriesListResponse -> c CountriesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CountriesListResponse #

toConstr :: CountriesListResponse -> Constr #

dataTypeOf :: CountriesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CountriesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CountriesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> CountriesListResponse -> CountriesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CountriesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CountriesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> CountriesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CountriesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CountriesListResponse -> m CountriesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CountriesListResponse -> m CountriesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CountriesListResponse -> m CountriesListResponse #

Show CountriesListResponse Source # 
Generic CountriesListResponse Source # 
ToJSON CountriesListResponse Source # 
FromJSON CountriesListResponse Source # 
type Rep CountriesListResponse Source # 
type Rep CountriesListResponse = D1 (MetaData "CountriesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CountriesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_couKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_couCountries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Country])))))

countriesListResponse :: CountriesListResponse Source #

Creates a value of CountriesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

couKind :: Lens' CountriesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#countriesListResponse".

AccountPermissionGroupsListResponse

data AccountPermissionGroupsListResponse Source #

Account Permission Group List Response

See: accountPermissionGroupsListResponse smart constructor.

Instances

Eq AccountPermissionGroupsListResponse Source # 
Data AccountPermissionGroupsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountPermissionGroupsListResponse -> c AccountPermissionGroupsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountPermissionGroupsListResponse #

toConstr :: AccountPermissionGroupsListResponse -> Constr #

dataTypeOf :: AccountPermissionGroupsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountPermissionGroupsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountPermissionGroupsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> AccountPermissionGroupsListResponse -> AccountPermissionGroupsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountPermissionGroupsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountPermissionGroupsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountPermissionGroupsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountPermissionGroupsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountPermissionGroupsListResponse -> m AccountPermissionGroupsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountPermissionGroupsListResponse -> m AccountPermissionGroupsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountPermissionGroupsListResponse -> m AccountPermissionGroupsListResponse #

Show AccountPermissionGroupsListResponse Source # 
Generic AccountPermissionGroupsListResponse Source # 
ToJSON AccountPermissionGroupsListResponse Source # 
FromJSON AccountPermissionGroupsListResponse Source # 
type Rep AccountPermissionGroupsListResponse Source # 
type Rep AccountPermissionGroupsListResponse = D1 (MetaData "AccountPermissionGroupsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AccountPermissionGroupsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_apglrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_apglrAccountPermissionGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AccountPermissionGroup])))))

accountPermissionGroupsListResponse :: AccountPermissionGroupsListResponse Source #

Creates a value of AccountPermissionGroupsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

apglrKind :: Lens' AccountPermissionGroupsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#accountPermissionGroupsListResponse".

PopupWindowProperties

data PopupWindowProperties Source #

Popup Window Properties.

See: popupWindowProperties smart constructor.

Instances

Eq PopupWindowProperties Source # 
Data PopupWindowProperties Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PopupWindowProperties -> c PopupWindowProperties #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PopupWindowProperties #

toConstr :: PopupWindowProperties -> Constr #

dataTypeOf :: PopupWindowProperties -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PopupWindowProperties) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PopupWindowProperties) #

gmapT :: (forall b. Data b => b -> b) -> PopupWindowProperties -> PopupWindowProperties #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PopupWindowProperties -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PopupWindowProperties -> r #

gmapQ :: (forall d. Data d => d -> u) -> PopupWindowProperties -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PopupWindowProperties -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PopupWindowProperties -> m PopupWindowProperties #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PopupWindowProperties -> m PopupWindowProperties #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PopupWindowProperties -> m PopupWindowProperties #

Show PopupWindowProperties Source # 
Generic PopupWindowProperties Source # 
ToJSON PopupWindowProperties Source # 
FromJSON PopupWindowProperties Source # 
type Rep PopupWindowProperties Source # 

popupWindowProperties :: PopupWindowProperties Source #

Creates a value of PopupWindowProperties with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pwpOffSet :: Lens' PopupWindowProperties (Maybe OffSetPosition) Source #

Upper-left corner coordinates of the popup window. Applicable if positionType is COORDINATES.

pwpDimension :: Lens' PopupWindowProperties (Maybe Size) Source #

Popup dimension for a creative. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA and all VPAID

pwpShowStatusBar :: Lens' PopupWindowProperties (Maybe Bool) Source #

Whether to display the browser status bar.

pwpShowMenuBar :: Lens' PopupWindowProperties (Maybe Bool) Source #

Whether to display the browser menu bar.

pwpPositionType :: Lens' PopupWindowProperties (Maybe PopupWindowPropertiesPositionType) Source #

Popup window position either centered or at specific coordinate.

pwpShowAddressBar :: Lens' PopupWindowProperties (Maybe Bool) Source #

Whether to display the browser address bar.

pwpShowScrollBar :: Lens' PopupWindowProperties (Maybe Bool) Source #

Whether to display the browser scroll bar.

pwpShowToolBar :: Lens' PopupWindowProperties (Maybe Bool) Source #

Whether to display the browser tool bar.

CreativeAssetDetectedFeaturesItem

data CreativeAssetDetectedFeaturesItem Source #

Constructors

CADFIApplicationCache
APPLICATION_CACHE
CADFIAudio
AUDIO
CADFICanvas
CANVAS
CADFICanvasText
CANVAS_TEXT
CADFICssAnimations
CSS_ANIMATIONS
CADFICssBackgRoundSize
CSS_BACKGROUND_SIZE
CADFICssBOrderImage
CSS_BORDER_IMAGE
CADFICssBOrderRadius
CSS_BORDER_RADIUS
CADFICssBoxShadow
CSS_BOX_SHADOW
CADFICssColumns
CSS_COLUMNS
CADFICssFlexBox
CSS_FLEX_BOX
CADFICssFontFace
CSS_FONT_FACE
CADFICssGeneratedContent
CSS_GENERATED_CONTENT
CADFICssGradients
CSS_GRADIENTS
CADFICssHsla
CSS_HSLA
CADFICssMultipleBgs
CSS_MULTIPLE_BGS
CADFICssOpacity
CSS_OPACITY
CADFICssReflections
CSS_REFLECTIONS
CADFICssRgba
CSS_RGBA
CADFICssTextShadow
CSS_TEXT_SHADOW
CADFICssTransforms
CSS_TRANSFORMS
CADFICssTRANSFORMS3D
CSS_TRANSFORMS3D
CADFICssTransitions
CSS_TRANSITIONS
CADFIDragAndDrop
DRAG_AND_DROP
CADFIGeoLocation
GEO_LOCATION
CADFIHashChange
HASH_CHANGE
CADFIHistory
HISTORY
CADFIIndexedDB
INDEXED_DB
CADFIInlineSvg
INLINE_SVG
CADFIInputAttrAutocomplete
INPUT_ATTR_AUTOCOMPLETE
CADFIInputAttrAutofocus
INPUT_ATTR_AUTOFOCUS
CADFIInputAttrList
INPUT_ATTR_LIST
CADFIInputAttrMax
INPUT_ATTR_MAX
CADFIInputAttrMin
INPUT_ATTR_MIN
CADFIInputAttrMultiple
INPUT_ATTR_MULTIPLE
CADFIInputAttrPattern
INPUT_ATTR_PATTERN
CADFIInputAttrPlaceholder
INPUT_ATTR_PLACEHOLDER
CADFIInputAttrRequired
INPUT_ATTR_REQUIRED
CADFIInputAttrStep
INPUT_ATTR_STEP
CADFIInputTypeColor
INPUT_TYPE_COLOR
CADFIInputTypeDate
INPUT_TYPE_DATE
CADFIInputTypeDatetime
INPUT_TYPE_DATETIME
CADFIInputTypeDatetimeLocal
INPUT_TYPE_DATETIME_LOCAL
CADFIInputTypeEmail
INPUT_TYPE_EMAIL
CADFIInputTypeMonth
INPUT_TYPE_MONTH
CADFIInputTypeNumber
INPUT_TYPE_NUMBER
CADFIInputTypeRange
INPUT_TYPE_RANGE
CADFIInputTypeSearch
INPUT_TYPE_SEARCH
CADFIInputTypeTel
INPUT_TYPE_TEL
CADFIInputTypeTime
INPUT_TYPE_TIME
CADFIInputTypeURL
INPUT_TYPE_URL
CADFIInputTypeWeek
INPUT_TYPE_WEEK
CADFILocalStorage
LOCAL_STORAGE
CADFIPostMessage
POST_MESSAGE
CADFISessionStorage
SESSION_STORAGE
CADFISmil
SMIL
CADFISvgClipPaths
SVG_CLIP_PATHS
CADFISvgFeImage
SVG_FE_IMAGE
CADFISvgFilters
SVG_FILTERS
CADFISvgHref
SVG_HREF
CADFITouch
TOUCH
CADFIVideo
VIDEO
CADFIWebgl
WEBGL
CADFIWebSockets
WEB_SOCKETS
CADFIWebSQLDatabase
WEB_SQL_DATABASE
CADFIWebWorkers
WEB_WORKERS

Instances

Enum CreativeAssetDetectedFeaturesItem Source # 
Eq CreativeAssetDetectedFeaturesItem Source # 
Data CreativeAssetDetectedFeaturesItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetDetectedFeaturesItem -> c CreativeAssetDetectedFeaturesItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetDetectedFeaturesItem #

toConstr :: CreativeAssetDetectedFeaturesItem -> Constr #

dataTypeOf :: CreativeAssetDetectedFeaturesItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetDetectedFeaturesItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetDetectedFeaturesItem) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetDetectedFeaturesItem -> CreativeAssetDetectedFeaturesItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetDetectedFeaturesItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetDetectedFeaturesItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetDetectedFeaturesItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetDetectedFeaturesItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetDetectedFeaturesItem -> m CreativeAssetDetectedFeaturesItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetDetectedFeaturesItem -> m CreativeAssetDetectedFeaturesItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetDetectedFeaturesItem -> m CreativeAssetDetectedFeaturesItem #

Ord CreativeAssetDetectedFeaturesItem Source # 
Read CreativeAssetDetectedFeaturesItem Source # 
Show CreativeAssetDetectedFeaturesItem Source # 
Generic CreativeAssetDetectedFeaturesItem Source # 
Hashable CreativeAssetDetectedFeaturesItem Source # 
ToJSON CreativeAssetDetectedFeaturesItem Source # 
FromJSON CreativeAssetDetectedFeaturesItem Source # 
FromHttpApiData CreativeAssetDetectedFeaturesItem Source # 
ToHttpApiData CreativeAssetDetectedFeaturesItem Source # 
type Rep CreativeAssetDetectedFeaturesItem Source # 
type Rep CreativeAssetDetectedFeaturesItem = D1 (MetaData "CreativeAssetDetectedFeaturesItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CADFIApplicationCache" PrefixI False) U1) (C1 (MetaCons "CADFIAudio" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFICanvas" PrefixI False) U1) (C1 (MetaCons "CADFICanvasText" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CADFICssAnimations" PrefixI False) U1) (C1 (MetaCons "CADFICssBackgRoundSize" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFICssBOrderImage" PrefixI False) U1) (C1 (MetaCons "CADFICssBOrderRadius" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CADFICssBoxShadow" PrefixI False) U1) (C1 (MetaCons "CADFICssColumns" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFICssFlexBox" PrefixI False) U1) (C1 (MetaCons "CADFICssFontFace" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CADFICssGeneratedContent" PrefixI False) U1) (C1 (MetaCons "CADFICssGradients" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFICssHsla" PrefixI False) U1) (C1 (MetaCons "CADFICssMultipleBgs" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CADFICssOpacity" PrefixI False) U1) (C1 (MetaCons "CADFICssReflections" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFICssRgba" PrefixI False) U1) (C1 (MetaCons "CADFICssTextShadow" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CADFICssTransforms" PrefixI False) U1) (C1 (MetaCons "CADFICssTRANSFORMS3D" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFICssTransitions" PrefixI False) U1) (C1 (MetaCons "CADFIDragAndDrop" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CADFIGeoLocation" PrefixI False) U1) (C1 (MetaCons "CADFIHashChange" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFIHistory" PrefixI False) U1) (C1 (MetaCons "CADFIIndexedDB" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CADFIInlineSvg" PrefixI False) U1) (C1 (MetaCons "CADFIInputAttrAutocomplete" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFIInputAttrAutofocus" PrefixI False) U1) ((:+:) (C1 (MetaCons "CADFIInputAttrList" PrefixI False) U1) (C1 (MetaCons "CADFIInputAttrMax" PrefixI False) U1))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CADFIInputAttrMin" PrefixI False) U1) (C1 (MetaCons "CADFIInputAttrMultiple" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFIInputAttrPattern" PrefixI False) U1) (C1 (MetaCons "CADFIInputAttrPlaceholder" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CADFIInputAttrRequired" PrefixI False) U1) (C1 (MetaCons "CADFIInputAttrStep" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFIInputTypeColor" PrefixI False) U1) (C1 (MetaCons "CADFIInputTypeDate" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CADFIInputTypeDatetime" PrefixI False) U1) (C1 (MetaCons "CADFIInputTypeDatetimeLocal" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFIInputTypeEmail" PrefixI False) U1) (C1 (MetaCons "CADFIInputTypeMonth" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CADFIInputTypeNumber" PrefixI False) U1) (C1 (MetaCons "CADFIInputTypeRange" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFIInputTypeSearch" PrefixI False) U1) (C1 (MetaCons "CADFIInputTypeTel" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CADFIInputTypeTime" PrefixI False) U1) (C1 (MetaCons "CADFIInputTypeURL" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFIInputTypeWeek" PrefixI False) U1) (C1 (MetaCons "CADFILocalStorage" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CADFIPostMessage" PrefixI False) U1) (C1 (MetaCons "CADFISessionStorage" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFISmil" PrefixI False) U1) (C1 (MetaCons "CADFISvgClipPaths" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CADFISvgFeImage" PrefixI False) U1) (C1 (MetaCons "CADFISvgFilters" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFISvgHref" PrefixI False) U1) (C1 (MetaCons "CADFITouch" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CADFIVideo" PrefixI False) U1) (C1 (MetaCons "CADFIWebgl" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CADFIWebSockets" PrefixI False) U1) ((:+:) (C1 (MetaCons "CADFIWebSQLDatabase" PrefixI False) U1) (C1 (MetaCons "CADFIWebWorkers" PrefixI False) U1))))))))

FloodlightActivityGroupType

data FloodlightActivityGroupType Source #

Type of the floodlight activity group. This is a required field that is read-only after insertion.

Constructors

FAGTCounter
COUNTER
FAGTSale
SALE

Instances

Enum FloodlightActivityGroupType Source # 
Eq FloodlightActivityGroupType Source # 
Data FloodlightActivityGroupType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivityGroupType -> c FloodlightActivityGroupType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivityGroupType #

toConstr :: FloodlightActivityGroupType -> Constr #

dataTypeOf :: FloodlightActivityGroupType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivityGroupType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivityGroupType) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivityGroupType -> FloodlightActivityGroupType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityGroupType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityGroupType -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivityGroupType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivityGroupType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupType -> m FloodlightActivityGroupType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupType -> m FloodlightActivityGroupType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupType -> m FloodlightActivityGroupType #

Ord FloodlightActivityGroupType Source # 
Read FloodlightActivityGroupType Source # 
Show FloodlightActivityGroupType Source # 
Generic FloodlightActivityGroupType Source # 
Hashable FloodlightActivityGroupType Source # 
ToJSON FloodlightActivityGroupType Source # 
FromJSON FloodlightActivityGroupType Source # 
FromHttpApiData FloodlightActivityGroupType Source # 
ToHttpApiData FloodlightActivityGroupType Source # 
type Rep FloodlightActivityGroupType Source # 
type Rep FloodlightActivityGroupType = D1 (MetaData "FloodlightActivityGroupType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "FAGTCounter" PrefixI False) U1) (C1 (MetaCons "FAGTSale" PrefixI False) U1))

DirectorySiteContactType

data DirectorySiteContactType Source #

Directory site contact type.

Constructors

DSCTBilling
BILLING
DSCTOther
OTHER
DSCTSales
SALES
DSCTTechnical
TECHNICAL

Instances

Enum DirectorySiteContactType Source # 
Eq DirectorySiteContactType Source # 
Data DirectorySiteContactType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectorySiteContactType -> c DirectorySiteContactType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectorySiteContactType #

toConstr :: DirectorySiteContactType -> Constr #

dataTypeOf :: DirectorySiteContactType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectorySiteContactType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectorySiteContactType) #

gmapT :: (forall b. Data b => b -> b) -> DirectorySiteContactType -> DirectorySiteContactType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteContactType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteContactType -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectorySiteContactType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectorySiteContactType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectorySiteContactType -> m DirectorySiteContactType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteContactType -> m DirectorySiteContactType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteContactType -> m DirectorySiteContactType #

Ord DirectorySiteContactType Source # 
Read DirectorySiteContactType Source # 
Show DirectorySiteContactType Source # 
Generic DirectorySiteContactType Source # 
Hashable DirectorySiteContactType Source # 
ToJSON DirectorySiteContactType Source # 
FromJSON DirectorySiteContactType Source # 
FromHttpApiData DirectorySiteContactType Source # 
ToHttpApiData DirectorySiteContactType Source # 
type Rep DirectorySiteContactType Source # 
type Rep DirectorySiteContactType = D1 (MetaData "DirectorySiteContactType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "DSCTBilling" PrefixI False) U1) (C1 (MetaCons "DSCTOther" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DSCTSales" PrefixI False) U1) (C1 (MetaCons "DSCTTechnical" PrefixI False) U1)))

EventTagOverride

data EventTagOverride Source #

Event tag override information.

See: eventTagOverride smart constructor.

Instances

Eq EventTagOverride Source # 
Data EventTagOverride Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventTagOverride -> c EventTagOverride #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventTagOverride #

toConstr :: EventTagOverride -> Constr #

dataTypeOf :: EventTagOverride -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EventTagOverride) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventTagOverride) #

gmapT :: (forall b. Data b => b -> b) -> EventTagOverride -> EventTagOverride #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventTagOverride -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventTagOverride -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventTagOverride -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventTagOverride -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventTagOverride -> m EventTagOverride #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTagOverride -> m EventTagOverride #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTagOverride -> m EventTagOverride #

Show EventTagOverride Source # 
Generic EventTagOverride Source # 
ToJSON EventTagOverride Source # 
FromJSON EventTagOverride Source # 
type Rep EventTagOverride Source # 
type Rep EventTagOverride = D1 (MetaData "EventTagOverride" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "EventTagOverride'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_etoEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_etoId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))

eventTagOverride :: EventTagOverride Source #

Creates a value of EventTagOverride with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

etoEnabled :: Lens' EventTagOverride (Maybe Bool) Source #

Whether this override is enabled.

etoId :: Lens' EventTagOverride (Maybe Int64) Source #

ID of this event tag override. This is a read-only, auto-generated field.

PlacementsGeneratetagsTagFormats

data PlacementsGeneratetagsTagFormats Source #

Tag formats to generate for these placements.

Constructors

PGTFPlacementTagClickCommands
PLACEMENT_TAG_CLICK_COMMANDS
PGTFPlacementTagIframeIlayer
PLACEMENT_TAG_IFRAME_ILAYER
PGTFPlacementTagIframeJavascript
PLACEMENT_TAG_IFRAME_JAVASCRIPT
PGTFPlacementTagIframeJavascriptLegacy
PLACEMENT_TAG_IFRAME_JAVASCRIPT_LEGACY
PGTFPlacementTagInstreamVideoPrefetch
PLACEMENT_TAG_INSTREAM_VIDEO_PREFETCH
PGTFPlacementTagInstreamVideoPrefetchVast3
PLACEMENT_TAG_INSTREAM_VIDEO_PREFETCH_VAST_3
PGTFPlacementTagInternalRedirect
PLACEMENT_TAG_INTERNAL_REDIRECT
PGTFPlacementTagInterstitialIframeJavascript
PLACEMENT_TAG_INTERSTITIAL_IFRAME_JAVASCRIPT
PGTFPlacementTagInterstitialIframeJavascriptLegacy
PLACEMENT_TAG_INTERSTITIAL_IFRAME_JAVASCRIPT_LEGACY
PGTFPlacementTagInterstitialInternalRedirect
PLACEMENT_TAG_INTERSTITIAL_INTERNAL_REDIRECT
PGTFPlacementTagInterstitialJavascript
PLACEMENT_TAG_INTERSTITIAL_JAVASCRIPT
PGTFPlacementTagInterstitialJavascriptLegacy
PLACEMENT_TAG_INTERSTITIAL_JAVASCRIPT_LEGACY
PGTFPlacementTagJavascript
PLACEMENT_TAG_JAVASCRIPT
PGTFPlacementTagJavascriptLegacy
PLACEMENT_TAG_JAVASCRIPT_LEGACY
PGTFPlacementTagStandard
PLACEMENT_TAG_STANDARD
PGTFPlacementTagTracking
PLACEMENT_TAG_TRACKING
PGTFPlacementTagTrackingIframe
PLACEMENT_TAG_TRACKING_IFRAME
PGTFPlacementTagTrackingJavascript
PLACEMENT_TAG_TRACKING_JAVASCRIPT

Instances

Enum PlacementsGeneratetagsTagFormats Source # 
Eq PlacementsGeneratetagsTagFormats Source # 
Data PlacementsGeneratetagsTagFormats Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementsGeneratetagsTagFormats -> c PlacementsGeneratetagsTagFormats #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementsGeneratetagsTagFormats #

toConstr :: PlacementsGeneratetagsTagFormats -> Constr #

dataTypeOf :: PlacementsGeneratetagsTagFormats -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementsGeneratetagsTagFormats) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementsGeneratetagsTagFormats) #

gmapT :: (forall b. Data b => b -> b) -> PlacementsGeneratetagsTagFormats -> PlacementsGeneratetagsTagFormats #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementsGeneratetagsTagFormats -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementsGeneratetagsTagFormats -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementsGeneratetagsTagFormats -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementsGeneratetagsTagFormats -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementsGeneratetagsTagFormats -> m PlacementsGeneratetagsTagFormats #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementsGeneratetagsTagFormats -> m PlacementsGeneratetagsTagFormats #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementsGeneratetagsTagFormats -> m PlacementsGeneratetagsTagFormats #

Ord PlacementsGeneratetagsTagFormats Source # 
Read PlacementsGeneratetagsTagFormats Source # 
Show PlacementsGeneratetagsTagFormats Source # 
Generic PlacementsGeneratetagsTagFormats Source # 
Hashable PlacementsGeneratetagsTagFormats Source # 
ToJSON PlacementsGeneratetagsTagFormats Source # 
FromJSON PlacementsGeneratetagsTagFormats Source # 
FromHttpApiData PlacementsGeneratetagsTagFormats Source # 
ToHttpApiData PlacementsGeneratetagsTagFormats Source # 
type Rep PlacementsGeneratetagsTagFormats Source # 
type Rep PlacementsGeneratetagsTagFormats = D1 (MetaData "PlacementsGeneratetagsTagFormats" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "PGTFPlacementTagClickCommands" PrefixI False) U1) (C1 (MetaCons "PGTFPlacementTagIframeIlayer" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PGTFPlacementTagIframeJavascript" PrefixI False) U1) (C1 (MetaCons "PGTFPlacementTagIframeJavascriptLegacy" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PGTFPlacementTagInstreamVideoPrefetch" PrefixI False) U1) (C1 (MetaCons "PGTFPlacementTagInstreamVideoPrefetchVast3" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PGTFPlacementTagInternalRedirect" PrefixI False) U1) ((:+:) (C1 (MetaCons "PGTFPlacementTagInterstitialIframeJavascript" PrefixI False) U1) (C1 (MetaCons "PGTFPlacementTagInterstitialIframeJavascriptLegacy" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "PGTFPlacementTagInterstitialInternalRedirect" PrefixI False) U1) (C1 (MetaCons "PGTFPlacementTagInterstitialJavascript" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PGTFPlacementTagInterstitialJavascriptLegacy" PrefixI False) U1) (C1 (MetaCons "PGTFPlacementTagJavascript" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PGTFPlacementTagJavascriptLegacy" PrefixI False) U1) (C1 (MetaCons "PGTFPlacementTagStandard" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PGTFPlacementTagTracking" PrefixI False) U1) ((:+:) (C1 (MetaCons "PGTFPlacementTagTrackingIframe" PrefixI False) U1) (C1 (MetaCons "PGTFPlacementTagTrackingJavascript" PrefixI False) U1))))))

AccountUserProFilesListSortField

data AccountUserProFilesListSortField Source #

Field by which to sort the list.

Constructors

AUPFLSFID
ID
AUPFLSFName
NAME

Instances

Enum AccountUserProFilesListSortField Source # 
Eq AccountUserProFilesListSortField Source # 
Data AccountUserProFilesListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountUserProFilesListSortField -> c AccountUserProFilesListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountUserProFilesListSortField #

toConstr :: AccountUserProFilesListSortField -> Constr #

dataTypeOf :: AccountUserProFilesListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountUserProFilesListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountUserProFilesListSortField) #

gmapT :: (forall b. Data b => b -> b) -> AccountUserProFilesListSortField -> AccountUserProFilesListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountUserProFilesListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountUserProFilesListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountUserProFilesListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountUserProFilesListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountUserProFilesListSortField -> m AccountUserProFilesListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountUserProFilesListSortField -> m AccountUserProFilesListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountUserProFilesListSortField -> m AccountUserProFilesListSortField #

Ord AccountUserProFilesListSortField Source # 
Read AccountUserProFilesListSortField Source # 
Show AccountUserProFilesListSortField Source # 
Generic AccountUserProFilesListSortField Source # 
Hashable AccountUserProFilesListSortField Source # 
ToJSON AccountUserProFilesListSortField Source # 
FromJSON AccountUserProFilesListSortField Source # 
FromHttpApiData AccountUserProFilesListSortField Source # 
ToHttpApiData AccountUserProFilesListSortField Source # 
type Rep AccountUserProFilesListSortField Source # 
type Rep AccountUserProFilesListSortField = D1 (MetaData "AccountUserProFilesListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "AUPFLSFID" PrefixI False) U1) (C1 (MetaCons "AUPFLSFName" PrefixI False) U1))

OperatingSystemVersion

data OperatingSystemVersion Source #

Contains information about a particular version of an operating system that can be targeted by ads.

See: operatingSystemVersion smart constructor.

Instances

Eq OperatingSystemVersion Source # 
Data OperatingSystemVersion Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OperatingSystemVersion -> c OperatingSystemVersion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OperatingSystemVersion #

toConstr :: OperatingSystemVersion -> Constr #

dataTypeOf :: OperatingSystemVersion -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OperatingSystemVersion) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OperatingSystemVersion) #

gmapT :: (forall b. Data b => b -> b) -> OperatingSystemVersion -> OperatingSystemVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OperatingSystemVersion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OperatingSystemVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> OperatingSystemVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OperatingSystemVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OperatingSystemVersion -> m OperatingSystemVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OperatingSystemVersion -> m OperatingSystemVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OperatingSystemVersion -> m OperatingSystemVersion #

Show OperatingSystemVersion Source # 
Generic OperatingSystemVersion Source # 
ToJSON OperatingSystemVersion Source # 
FromJSON OperatingSystemVersion Source # 
type Rep OperatingSystemVersion Source # 
type Rep OperatingSystemVersion = D1 (MetaData "OperatingSystemVersion" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "OperatingSystemVersion'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_osvMinorVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_osvKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_osvOperatingSystem") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe OperatingSystem))))) ((:*:) (S1 (MetaSel (Just Symbol "_osvMajorVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_osvName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_osvId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))))

operatingSystemVersion :: OperatingSystemVersion Source #

Creates a value of OperatingSystemVersion with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

osvMinorVersion :: Lens' OperatingSystemVersion (Maybe Text) Source #

Minor version (number after the first dot) of this operating system version.

osvKind :: Lens' OperatingSystemVersion Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#operatingSystemVersion".

osvOperatingSystem :: Lens' OperatingSystemVersion (Maybe OperatingSystem) Source #

Operating system of this operating system version.

osvMajorVersion :: Lens' OperatingSystemVersion (Maybe Text) Source #

Major version (leftmost number) of this operating system version.

osvName :: Lens' OperatingSystemVersion (Maybe Text) Source #

Name of this operating system version.

osvId :: Lens' OperatingSystemVersion (Maybe Int64) Source #

ID of this operating system version.

InventoryItemsListSortOrder

data InventoryItemsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

IILSOAscending
ASCENDING
IILSODescending
DESCENDING

Instances

Enum InventoryItemsListSortOrder Source # 
Eq InventoryItemsListSortOrder Source # 
Data InventoryItemsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InventoryItemsListSortOrder -> c InventoryItemsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InventoryItemsListSortOrder #

toConstr :: InventoryItemsListSortOrder -> Constr #

dataTypeOf :: InventoryItemsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InventoryItemsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InventoryItemsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> InventoryItemsListSortOrder -> InventoryItemsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InventoryItemsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InventoryItemsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> InventoryItemsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InventoryItemsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InventoryItemsListSortOrder -> m InventoryItemsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryItemsListSortOrder -> m InventoryItemsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InventoryItemsListSortOrder -> m InventoryItemsListSortOrder #

Ord InventoryItemsListSortOrder Source # 
Read InventoryItemsListSortOrder Source # 
Show InventoryItemsListSortOrder Source # 
Generic InventoryItemsListSortOrder Source # 
Hashable InventoryItemsListSortOrder Source # 
ToJSON InventoryItemsListSortOrder Source # 
FromJSON InventoryItemsListSortOrder Source # 
FromHttpApiData InventoryItemsListSortOrder Source # 
ToHttpApiData InventoryItemsListSortOrder Source # 
type Rep InventoryItemsListSortOrder Source # 
type Rep InventoryItemsListSortOrder = D1 (MetaData "InventoryItemsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "IILSOAscending" PrefixI False) U1) (C1 (MetaCons "IILSODescending" PrefixI False) U1))

PlacementStrategiesListSortOrder

data PlacementStrategiesListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

PSLSOAscending
ASCENDING
PSLSODescending
DESCENDING

Instances

Enum PlacementStrategiesListSortOrder Source # 
Eq PlacementStrategiesListSortOrder Source # 
Data PlacementStrategiesListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementStrategiesListSortOrder -> c PlacementStrategiesListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementStrategiesListSortOrder #

toConstr :: PlacementStrategiesListSortOrder -> Constr #

dataTypeOf :: PlacementStrategiesListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementStrategiesListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementStrategiesListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> PlacementStrategiesListSortOrder -> PlacementStrategiesListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementStrategiesListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementStrategiesListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementStrategiesListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementStrategiesListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementStrategiesListSortOrder -> m PlacementStrategiesListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementStrategiesListSortOrder -> m PlacementStrategiesListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementStrategiesListSortOrder -> m PlacementStrategiesListSortOrder #

Ord PlacementStrategiesListSortOrder Source # 
Read PlacementStrategiesListSortOrder Source # 
Show PlacementStrategiesListSortOrder Source # 
Generic PlacementStrategiesListSortOrder Source # 
Hashable PlacementStrategiesListSortOrder Source # 
ToJSON PlacementStrategiesListSortOrder Source # 
FromJSON PlacementStrategiesListSortOrder Source # 
FromHttpApiData PlacementStrategiesListSortOrder Source # 
ToHttpApiData PlacementStrategiesListSortOrder Source # 
type Rep PlacementStrategiesListSortOrder Source # 
type Rep PlacementStrategiesListSortOrder = D1 (MetaData "PlacementStrategiesListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PSLSOAscending" PrefixI False) U1) (C1 (MetaCons "PSLSODescending" PrefixI False) U1))

AccountPermission

data AccountPermission Source #

AccountPermissions contains information about a particular account permission. Some features of DCM require an account permission to be present in the account.

See: accountPermission smart constructor.

Instances

Eq AccountPermission Source # 
Data AccountPermission Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountPermission -> c AccountPermission #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountPermission #

toConstr :: AccountPermission -> Constr #

dataTypeOf :: AccountPermission -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountPermission) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountPermission) #

gmapT :: (forall b. Data b => b -> b) -> AccountPermission -> AccountPermission #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountPermission -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountPermission -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountPermission -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountPermission -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountPermission -> m AccountPermission #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountPermission -> m AccountPermission #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountPermission -> m AccountPermission #

Show AccountPermission Source # 
Generic AccountPermission Source # 
ToJSON AccountPermission Source # 
FromJSON AccountPermission Source # 
type Rep AccountPermission Source # 

accountPermission :: AccountPermission Source #

Creates a value of AccountPermission with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

acccKind :: Lens' AccountPermission Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#accountPermission".

acccAccountProFiles :: Lens' AccountPermission [AccountPermissionAccountProFilesItem] Source #

Account profiles associated with this account permission. Possible values are: - "ACCOUNT_PROFILE_BASIC" - "ACCOUNT_PROFILE_STANDARD"

acccName :: Lens' AccountPermission (Maybe Text) Source #

Name of this account permission.

acccId :: Lens' AccountPermission (Maybe Int64) Source #

ID of this account permission.

acccLevel :: Lens' AccountPermission (Maybe AccountPermissionLevel) Source #

Administrative level required to enable this account permission.

acccPermissionGroupId :: Lens' AccountPermission (Maybe Int64) Source #

Permission group of this account permission.

UserProFile

data UserProFile Source #

Represents a UserProfile resource.

See: userProFile smart constructor.

Instances

Eq UserProFile Source # 
Data UserProFile Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserProFile -> c UserProFile #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserProFile #

toConstr :: UserProFile -> Constr #

dataTypeOf :: UserProFile -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserProFile) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserProFile) #

gmapT :: (forall b. Data b => b -> b) -> UserProFile -> UserProFile #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserProFile -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserProFile -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserProFile -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserProFile -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserProFile -> m UserProFile #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserProFile -> m UserProFile #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserProFile -> m UserProFile #

Show UserProFile Source # 
Generic UserProFile Source # 

Associated Types

type Rep UserProFile :: * -> * #

ToJSON UserProFile Source # 
FromJSON UserProFile Source # 
type Rep UserProFile Source # 

userProFile :: UserProFile Source #

Creates a value of UserProFile with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

upfEtag :: Lens' UserProFile (Maybe Text) Source #

The eTag of this response for caching purposes.

upfKind :: Lens' UserProFile Text Source #

The kind of resource this is, in this case dfareporting#userProfile.

upfAccountName :: Lens' UserProFile (Maybe Text) Source #

The account name this profile belongs to.

upfProFileId :: Lens' UserProFile (Maybe Int64) Source #

The unique ID of the user profile.

upfAccountId :: Lens' UserProFile (Maybe Int64) Source #

The account ID to which this profile belongs.

upfSubAccountName :: Lens' UserProFile (Maybe Text) Source #

The sub account name this profile belongs to if applicable.

upfSubAccountId :: Lens' UserProFile (Maybe Int64) Source #

The sub account ID this profile belongs to if applicable.

OperatingSystemsListResponse

data OperatingSystemsListResponse Source #

Operating System List Response

See: operatingSystemsListResponse smart constructor.

Instances

Eq OperatingSystemsListResponse Source # 
Data OperatingSystemsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OperatingSystemsListResponse -> c OperatingSystemsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OperatingSystemsListResponse #

toConstr :: OperatingSystemsListResponse -> Constr #

dataTypeOf :: OperatingSystemsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OperatingSystemsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OperatingSystemsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> OperatingSystemsListResponse -> OperatingSystemsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OperatingSystemsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OperatingSystemsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> OperatingSystemsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OperatingSystemsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OperatingSystemsListResponse -> m OperatingSystemsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OperatingSystemsListResponse -> m OperatingSystemsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OperatingSystemsListResponse -> m OperatingSystemsListResponse #

Show OperatingSystemsListResponse Source # 
Generic OperatingSystemsListResponse Source # 
ToJSON OperatingSystemsListResponse Source # 
FromJSON OperatingSystemsListResponse Source # 
type Rep OperatingSystemsListResponse Source # 
type Rep OperatingSystemsListResponse = D1 (MetaData "OperatingSystemsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "OperatingSystemsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_oslrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_oslrOperatingSystems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [OperatingSystem])))))

operatingSystemsListResponse :: OperatingSystemsListResponse Source #

Creates a value of OperatingSystemsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

oslrKind :: Lens' OperatingSystemsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#operatingSystemsListResponse".

ReportDelivery

data ReportDelivery Source #

The report's email delivery settings.

See: reportDelivery smart constructor.

Instances

Eq ReportDelivery Source # 
Data ReportDelivery Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportDelivery -> c ReportDelivery #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportDelivery #

toConstr :: ReportDelivery -> Constr #

dataTypeOf :: ReportDelivery -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportDelivery) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportDelivery) #

gmapT :: (forall b. Data b => b -> b) -> ReportDelivery -> ReportDelivery #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportDelivery -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportDelivery -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportDelivery -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportDelivery -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportDelivery -> m ReportDelivery #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportDelivery -> m ReportDelivery #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportDelivery -> m ReportDelivery #

Show ReportDelivery Source # 
Generic ReportDelivery Source # 

Associated Types

type Rep ReportDelivery :: * -> * #

ToJSON ReportDelivery Source # 
FromJSON ReportDelivery Source # 
type Rep ReportDelivery Source # 
type Rep ReportDelivery = D1 (MetaData "ReportDelivery" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ReportDelivery'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rdEmailOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_rdRecipients") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Recipient])))) ((:*:) (S1 (MetaSel (Just Symbol "_rdMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rdEmailOwnerDeliveryType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportDeliveryEmailOwnerDeliveryType))))))

reportDelivery :: ReportDelivery Source #

Creates a value of ReportDelivery with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rdEmailOwner :: Lens' ReportDelivery (Maybe Bool) Source #

Whether the report should be emailed to the report owner.

rdRecipients :: Lens' ReportDelivery [Recipient] Source #

The list of recipients to which to email the report.

rdMessage :: Lens' ReportDelivery (Maybe Text) Source #

The message to be sent with each email.

rdEmailOwnerDeliveryType :: Lens' ReportDelivery (Maybe ReportDeliveryEmailOwnerDeliveryType) Source #

The type of delivery for the owner to receive, if enabled.

TargetableRemarketingList

data TargetableRemarketingList Source #

Contains properties of a targetable remarketing list. Remarketing enables you to create lists of users who have performed specific actions on a site, then target ads to members of those lists. This resource is a read-only view of a remarketing list to be used to faciliate targeting ads to specific lists. Remarketing lists that are owned by your advertisers and those that are shared to your advertisers or account are accessible via this resource. To manage remarketing lists that are owned by your advertisers, use the RemarketingLists resource.

See: targetableRemarketingList smart constructor.

Instances

Eq TargetableRemarketingList Source # 
Data TargetableRemarketingList Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TargetableRemarketingList -> c TargetableRemarketingList #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TargetableRemarketingList #

toConstr :: TargetableRemarketingList -> Constr #

dataTypeOf :: TargetableRemarketingList -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TargetableRemarketingList) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TargetableRemarketingList) #

gmapT :: (forall b. Data b => b -> b) -> TargetableRemarketingList -> TargetableRemarketingList #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TargetableRemarketingList -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TargetableRemarketingList -> r #

gmapQ :: (forall d. Data d => d -> u) -> TargetableRemarketingList -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TargetableRemarketingList -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TargetableRemarketingList -> m TargetableRemarketingList #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetableRemarketingList -> m TargetableRemarketingList #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetableRemarketingList -> m TargetableRemarketingList #

Show TargetableRemarketingList Source # 
Generic TargetableRemarketingList Source # 
ToJSON TargetableRemarketingList Source # 
FromJSON TargetableRemarketingList Source # 
type Rep TargetableRemarketingList Source # 
type Rep TargetableRemarketingList = D1 (MetaData "TargetableRemarketingList" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "TargetableRemarketingList'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_trlListSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_trlLifeSpan") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_trlKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_trlAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_trlAdvertiserIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_trlActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_trlAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_trlName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_trlListSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TargetableRemarketingListListSource))))) ((:*:) (S1 (MetaSel (Just Symbol "_trlId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_trlSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_trlDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

trlListSize :: Lens' TargetableRemarketingList (Maybe Int64) Source #

Number of users currently in the list. This is a read-only field.

trlLifeSpan :: Lens' TargetableRemarketingList (Maybe Int64) Source #

Number of days that a user should remain in the targetable remarketing list without an impression.

trlKind :: Lens' TargetableRemarketingList Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#targetableRemarketingList".

trlAdvertiserId :: Lens' TargetableRemarketingList (Maybe Int64) Source #

Dimension value for the advertiser ID that owns this targetable remarketing list.

trlActive :: Lens' TargetableRemarketingList (Maybe Bool) Source #

Whether this targetable remarketing list is active.

trlAccountId :: Lens' TargetableRemarketingList (Maybe Int64) Source #

Account ID of this remarketing list. This is a read-only, auto-generated field that is only returned in GET requests.

trlName :: Lens' TargetableRemarketingList (Maybe Text) Source #

Name of the targetable remarketing list. Is no greater than 128 characters long.

trlListSource :: Lens' TargetableRemarketingList (Maybe TargetableRemarketingListListSource) Source #

Product from which this targetable remarketing list was originated.

trlId :: Lens' TargetableRemarketingList (Maybe Int64) Source #

Targetable remarketing list ID.

trlSubAccountId :: Lens' TargetableRemarketingList (Maybe Int64) Source #

Subaccount ID of this remarketing list. This is a read-only, auto-generated field that is only returned in GET requests.

trlDescription :: Lens' TargetableRemarketingList (Maybe Text) Source #

Targetable remarketing list description.

ReportsFilesListSortField

data ReportsFilesListSortField Source #

The field by which to sort the list.

Constructors

RFLSFID

ID Sort by file ID.

RFLSFLastModifiedTime

LAST_MODIFIED_TIME Sort by 'lastmodifiedAt' field.

Instances

Enum ReportsFilesListSortField Source # 
Eq ReportsFilesListSortField Source # 
Data ReportsFilesListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportsFilesListSortField -> c ReportsFilesListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportsFilesListSortField #

toConstr :: ReportsFilesListSortField -> Constr #

dataTypeOf :: ReportsFilesListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportsFilesListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportsFilesListSortField) #

gmapT :: (forall b. Data b => b -> b) -> ReportsFilesListSortField -> ReportsFilesListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportsFilesListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportsFilesListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportsFilesListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportsFilesListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportsFilesListSortField -> m ReportsFilesListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportsFilesListSortField -> m ReportsFilesListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportsFilesListSortField -> m ReportsFilesListSortField #

Ord ReportsFilesListSortField Source # 
Read ReportsFilesListSortField Source # 
Show ReportsFilesListSortField Source # 
Generic ReportsFilesListSortField Source # 
Hashable ReportsFilesListSortField Source # 
ToJSON ReportsFilesListSortField Source # 
FromJSON ReportsFilesListSortField Source # 
FromHttpApiData ReportsFilesListSortField Source # 
ToHttpApiData ReportsFilesListSortField Source # 
type Rep ReportsFilesListSortField Source # 
type Rep ReportsFilesListSortField = D1 (MetaData "ReportsFilesListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "RFLSFID" PrefixI False) U1) (C1 (MetaCons "RFLSFLastModifiedTime" PrefixI False) U1))

PostalCodesListResponse

data PostalCodesListResponse Source #

Postal Code List Response

See: postalCodesListResponse smart constructor.

Instances

Eq PostalCodesListResponse Source # 
Data PostalCodesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PostalCodesListResponse -> c PostalCodesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PostalCodesListResponse #

toConstr :: PostalCodesListResponse -> Constr #

dataTypeOf :: PostalCodesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PostalCodesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PostalCodesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> PostalCodesListResponse -> PostalCodesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PostalCodesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PostalCodesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> PostalCodesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PostalCodesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PostalCodesListResponse -> m PostalCodesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PostalCodesListResponse -> m PostalCodesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PostalCodesListResponse -> m PostalCodesListResponse #

Show PostalCodesListResponse Source # 
Generic PostalCodesListResponse Source # 
ToJSON PostalCodesListResponse Source # 
FromJSON PostalCodesListResponse Source # 
type Rep PostalCodesListResponse Source # 
type Rep PostalCodesListResponse = D1 (MetaData "PostalCodesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PostalCodesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pclrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_pclrPostalCodes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PostalCode])))))

postalCodesListResponse :: PostalCodesListResponse Source #

Creates a value of PostalCodesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pclrKind :: Lens' PostalCodesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#postalCodesListResponse".

ChangeLog

data ChangeLog Source #

Describes a change that a user has made to a resource.

See: changeLog smart constructor.

Instances

Eq ChangeLog Source # 
Data ChangeLog Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChangeLog -> c ChangeLog #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChangeLog #

toConstr :: ChangeLog -> Constr #

dataTypeOf :: ChangeLog -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChangeLog) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChangeLog) #

gmapT :: (forall b. Data b => b -> b) -> ChangeLog -> ChangeLog #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChangeLog -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChangeLog -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChangeLog -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChangeLog -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChangeLog -> m ChangeLog #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeLog -> m ChangeLog #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeLog -> m ChangeLog #

Show ChangeLog Source # 
Generic ChangeLog Source # 

Associated Types

type Rep ChangeLog :: * -> * #

ToJSON ChangeLog Source # 
FromJSON ChangeLog Source # 
type Rep ChangeLog Source # 
type Rep ChangeLog = D1 (MetaData "ChangeLog" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ChangeLog'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_chaUserProFileId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_chaObjectType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_chaUserProFileName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_chaKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_chaObjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_chaAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_chaTransactionId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_chaOldValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_chaAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_chaNewValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_chaFieldName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_chaId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_chaSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_chaChangeTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))))))))

changeLog :: ChangeLog Source #

Creates a value of ChangeLog with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

chaUserProFileId :: Lens' ChangeLog (Maybe Int64) Source #

ID of the user who modified the object.

chaObjectType :: Lens' ChangeLog (Maybe Text) Source #

Object type of the change log.

chaUserProFileName :: Lens' ChangeLog (Maybe Text) Source #

User profile name of the user who modified the object.

chaKind :: Lens' ChangeLog Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#changeLog".

chaObjectId :: Lens' ChangeLog (Maybe Int64) Source #

ID of the object of this change log. The object could be a campaign, placement, ad, or other type.

chaAction :: Lens' ChangeLog (Maybe Text) Source #

Action which caused the change.

chaTransactionId :: Lens' ChangeLog (Maybe Int64) Source #

Transaction ID of this change log. When a single API call results in many changes, each change will have a separate ID in the change log but will share the same transactionId.

chaOldValue :: Lens' ChangeLog (Maybe Text) Source #

Old value of the object field.

chaAccountId :: Lens' ChangeLog (Maybe Int64) Source #

Account ID of the modified object.

chaNewValue :: Lens' ChangeLog (Maybe Text) Source #

New value of the object field.

chaFieldName :: Lens' ChangeLog (Maybe Text) Source #

Field name of the object which changed.

chaId :: Lens' ChangeLog (Maybe Int64) Source #

ID of this change log.

chaSubAccountId :: Lens' ChangeLog (Maybe Int64) Source #

Subaccount ID of the modified object.

chaChangeTime :: Lens' ChangeLog (Maybe UTCTime) Source #

Time when the object was modified.

CreativesListSortField

data CreativesListSortField Source #

Field by which to sort the list.

Constructors

CID
ID
CName
NAME

Instances

Enum CreativesListSortField Source # 
Eq CreativesListSortField Source # 
Data CreativesListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativesListSortField -> c CreativesListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativesListSortField #

toConstr :: CreativesListSortField -> Constr #

dataTypeOf :: CreativesListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativesListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativesListSortField) #

gmapT :: (forall b. Data b => b -> b) -> CreativesListSortField -> CreativesListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativesListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativesListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativesListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativesListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativesListSortField -> m CreativesListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativesListSortField -> m CreativesListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativesListSortField -> m CreativesListSortField #

Ord CreativesListSortField Source # 
Read CreativesListSortField Source # 
Show CreativesListSortField Source # 
Generic CreativesListSortField Source # 
Hashable CreativesListSortField Source # 
ToJSON CreativesListSortField Source # 
FromJSON CreativesListSortField Source # 
FromHttpApiData CreativesListSortField Source # 
ToHttpApiData CreativesListSortField Source # 
type Rep CreativesListSortField Source # 
type Rep CreativesListSortField = D1 (MetaData "CreativesListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CID" PrefixI False) U1) (C1 (MetaCons "CName" PrefixI False) U1))

PlacementStrategy

data PlacementStrategy Source #

Contains properties of a placement strategy.

See: placementStrategy smart constructor.

Instances

Eq PlacementStrategy Source # 
Data PlacementStrategy Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementStrategy -> c PlacementStrategy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementStrategy #

toConstr :: PlacementStrategy -> Constr #

dataTypeOf :: PlacementStrategy -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementStrategy) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementStrategy) #

gmapT :: (forall b. Data b => b -> b) -> PlacementStrategy -> PlacementStrategy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementStrategy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementStrategy -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementStrategy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementStrategy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementStrategy -> m PlacementStrategy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementStrategy -> m PlacementStrategy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementStrategy -> m PlacementStrategy #

Show PlacementStrategy Source # 
Generic PlacementStrategy Source # 
ToJSON PlacementStrategy Source # 
FromJSON PlacementStrategy Source # 
type Rep PlacementStrategy Source # 
type Rep PlacementStrategy = D1 (MetaData "PlacementStrategy" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PlacementStrategy'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_psKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_psAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_psName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_psId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

placementStrategy :: PlacementStrategy Source #

Creates a value of PlacementStrategy with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

psKind :: Lens' PlacementStrategy Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#placementStrategy".

psAccountId :: Lens' PlacementStrategy (Maybe Int64) Source #

Account ID of this placement strategy.This is a read-only field that can be left blank.

psName :: Lens' PlacementStrategy (Maybe Text) Source #

Name of this placement strategy. This is a required field. It must be less than 256 characters long and unique among placement strategies of the same account.

psId :: Lens' PlacementStrategy (Maybe Int64) Source #

ID of this placement strategy. This is a read-only, auto-generated field.

FloodlightActivity

data FloodlightActivity Source #

Contains properties of a Floodlight activity.

See: floodlightActivity smart constructor.

Instances

Eq FloodlightActivity Source # 
Data FloodlightActivity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivity -> c FloodlightActivity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivity #

toConstr :: FloodlightActivity -> Constr #

dataTypeOf :: FloodlightActivity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivity) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivity -> FloodlightActivity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivity -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivity -> m FloodlightActivity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivity -> m FloodlightActivity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivity -> m FloodlightActivity #

Show FloodlightActivity Source # 
Generic FloodlightActivity Source # 
ToJSON FloodlightActivity Source # 
FromJSON FloodlightActivity Source # 
type Rep FloodlightActivity Source # 
type Rep FloodlightActivity = D1 (MetaData "FloodlightActivity" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FloodlightActivity'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faCountingMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FloodlightActivityCountingMethod))) ((:*:) (S1 (MetaSel (Just Symbol "_faTagString") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_faSecure") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faExpectedURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_faFloodlightActivityGroupTagString") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_faFloodlightConfigurationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_faKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faImageTagEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_faAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_faAdvertiserIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faSSLCompliant") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_faIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue)))) ((:*:) (S1 (MetaSel (Just Symbol "_faTagFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FloodlightActivityTagFormat))) (S1 (MetaSel (Just Symbol "_faCacheBustingType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FloodlightActivityCacheBustingType))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_faName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_faPublisherTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [FloodlightActivityPublisherDynamicTag]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faFloodlightActivityGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_faHidden") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_faFloodlightActivityGroupType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FloodlightActivityFloodlightActivityGroupType))) (S1 (MetaSel (Just Symbol "_faDefaultTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [FloodlightActivityDynamicTag])))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faFloodlightActivityGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_faId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_faSSLRequired") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faUserDefinedVariableTypes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [FloodlightActivityUserDefinedVariableTypesItem]))) (S1 (MetaSel (Just Symbol "_faSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_faNotes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_faFloodlightConfigurationIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue)))))))))

faCountingMethod :: Lens' FloodlightActivity (Maybe FloodlightActivityCountingMethod) Source #

Counting method for conversions for this floodlight activity. This is a required field.

faTagString :: Lens' FloodlightActivity (Maybe Text) Source #

Value of the cat= paramter in the floodlight tag, which the ad servers use to identify the activity. This is optional: if empty, a new tag string will be generated for you. This string must be 1 to 8 characters long, with valid characters being [a-z][A-Z][0-9][-][ _ ]. This tag string must also be unique among activities of the same activity group. This field is read-only after insertion.

faSecure :: Lens' FloodlightActivity (Maybe Bool) Source #

Whether this tag should use SSL.

faExpectedURL :: Lens' FloodlightActivity (Maybe Text) Source #

URL where this tag will be deployed. If specified, must be less than 256 characters long.

faFloodlightActivityGroupTagString :: Lens' FloodlightActivity (Maybe Text) Source #

Tag string of the associated floodlight activity group. This is a read-only field.

faFloodlightConfigurationId :: Lens' FloodlightActivity (Maybe Int64) Source #

Floodlight configuration ID of this floodlight activity. If this field is left blank, the value will be copied over either from the activity group's floodlight configuration or from the existing activity's floodlight configuration.

faKind :: Lens' FloodlightActivity Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#floodlightActivity".

faImageTagEnabled :: Lens' FloodlightActivity (Maybe Bool) Source #

Whether the image tag is enabled for this activity.

faAdvertiserId :: Lens' FloodlightActivity (Maybe Int64) Source #

Advertiser ID of this floodlight activity. If this field is left blank, the value will be copied over either from the activity group's advertiser or the existing activity's advertiser.

faAdvertiserIdDimensionValue :: Lens' FloodlightActivity (Maybe DimensionValue) Source #

Dimension value for the ID of the advertiser. This is a read-only, auto-generated field.

faSSLCompliant :: Lens' FloodlightActivity (Maybe Bool) Source #

Whether the floodlight activity is SSL-compliant. This is a read-only field, its value detected by the system from the floodlight tags.

faIdDimensionValue :: Lens' FloodlightActivity (Maybe DimensionValue) Source #

Dimension value for the ID of this floodlight activity. This is a read-only, auto-generated field.

faTagFormat :: Lens' FloodlightActivity (Maybe FloodlightActivityTagFormat) Source #

Tag format type for the floodlight activity. If left blank, the tag format will default to HTML.

faCacheBustingType :: Lens' FloodlightActivity (Maybe FloodlightActivityCacheBustingType) Source #

Code type used for cache busting in the generated tag.

faAccountId :: Lens' FloodlightActivity (Maybe Int64) Source #

Account ID of this floodlight activity. This is a read-only field that can be left blank.

faName :: Lens' FloodlightActivity (Maybe Text) Source #

Name of this floodlight activity. This is a required field. Must be less than 129 characters long and cannot contain quotes.

faFloodlightActivityGroupId :: Lens' FloodlightActivity (Maybe Int64) Source #

Floodlight activity group ID of this floodlight activity. This is a required field.

faHidden :: Lens' FloodlightActivity (Maybe Bool) Source #

Whether this activity is archived.

faFloodlightActivityGroupType :: Lens' FloodlightActivity (Maybe FloodlightActivityFloodlightActivityGroupType) Source #

Type of the associated floodlight activity group. This is a read-only field.

faFloodlightActivityGroupName :: Lens' FloodlightActivity (Maybe Text) Source #

Name of the associated floodlight activity group. This is a read-only field.

faId :: Lens' FloodlightActivity (Maybe Int64) Source #

ID of this floodlight activity. This is a read-only, auto-generated field.

faSSLRequired :: Lens' FloodlightActivity (Maybe Bool) Source #

Whether this floodlight activity must be SSL-compliant.

faUserDefinedVariableTypes :: Lens' FloodlightActivity [FloodlightActivityUserDefinedVariableTypesItem] Source #

List of the user-defined variables used by this conversion tag. These map to the "u[1-20]=" in the tags. Each of these can have a user defined type. Acceptable values are: - "U1" - "U2" - "U3" - "U4" - "U5" - "U6" - "U7" - "U8" - "U9" - "U10" - "U11" - "U12" - "U13" - "U14" - "U15" - "U16" - "U17" - "U18" - "U19" - "U20"

faSubAccountId :: Lens' FloodlightActivity (Maybe Int64) Source #

Subaccount ID of this floodlight activity. This is a read-only field that can be left blank.

faNotes :: Lens' FloodlightActivity (Maybe Text) Source #

General notes or implementation instructions for the tag.

faFloodlightConfigurationIdDimensionValue :: Lens' FloodlightActivity (Maybe DimensionValue) Source #

Dimension value for the ID of the floodlight configuration. This is a read-only, auto-generated field.

DayPartTargetingDaysOfWeekItem

data DayPartTargetingDaysOfWeekItem Source #

Instances

Enum DayPartTargetingDaysOfWeekItem Source # 
Eq DayPartTargetingDaysOfWeekItem Source # 
Data DayPartTargetingDaysOfWeekItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DayPartTargetingDaysOfWeekItem -> c DayPartTargetingDaysOfWeekItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DayPartTargetingDaysOfWeekItem #

toConstr :: DayPartTargetingDaysOfWeekItem -> Constr #

dataTypeOf :: DayPartTargetingDaysOfWeekItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DayPartTargetingDaysOfWeekItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DayPartTargetingDaysOfWeekItem) #

gmapT :: (forall b. Data b => b -> b) -> DayPartTargetingDaysOfWeekItem -> DayPartTargetingDaysOfWeekItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DayPartTargetingDaysOfWeekItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DayPartTargetingDaysOfWeekItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> DayPartTargetingDaysOfWeekItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DayPartTargetingDaysOfWeekItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DayPartTargetingDaysOfWeekItem -> m DayPartTargetingDaysOfWeekItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DayPartTargetingDaysOfWeekItem -> m DayPartTargetingDaysOfWeekItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DayPartTargetingDaysOfWeekItem -> m DayPartTargetingDaysOfWeekItem #

Ord DayPartTargetingDaysOfWeekItem Source # 
Read DayPartTargetingDaysOfWeekItem Source # 
Show DayPartTargetingDaysOfWeekItem Source # 
Generic DayPartTargetingDaysOfWeekItem Source # 
Hashable DayPartTargetingDaysOfWeekItem Source # 
ToJSON DayPartTargetingDaysOfWeekItem Source # 
FromJSON DayPartTargetingDaysOfWeekItem Source # 
FromHttpApiData DayPartTargetingDaysOfWeekItem Source # 
ToHttpApiData DayPartTargetingDaysOfWeekItem Source # 
type Rep DayPartTargetingDaysOfWeekItem Source # 
type Rep DayPartTargetingDaysOfWeekItem = D1 (MetaData "DayPartTargetingDaysOfWeekItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "DPTDOWIFriday" PrefixI False) U1) ((:+:) (C1 (MetaCons "DPTDOWIMonday" PrefixI False) U1) (C1 (MetaCons "DPTDOWISaturday" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "DPTDOWISunday" PrefixI False) U1) (C1 (MetaCons "DPTDOWIThursday" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DPTDOWITuesday" PrefixI False) U1) (C1 (MetaCons "DPTDOWIWednesday" PrefixI False) U1))))

CustomFloodlightVariable

data CustomFloodlightVariable Source #

A custom floodlight variable.

See: customFloodlightVariable smart constructor.

Instances

Eq CustomFloodlightVariable Source # 
Data CustomFloodlightVariable Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CustomFloodlightVariable -> c CustomFloodlightVariable #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CustomFloodlightVariable #

toConstr :: CustomFloodlightVariable -> Constr #

dataTypeOf :: CustomFloodlightVariable -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CustomFloodlightVariable) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CustomFloodlightVariable) #

gmapT :: (forall b. Data b => b -> b) -> CustomFloodlightVariable -> CustomFloodlightVariable #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CustomFloodlightVariable -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CustomFloodlightVariable -> r #

gmapQ :: (forall d. Data d => d -> u) -> CustomFloodlightVariable -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CustomFloodlightVariable -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CustomFloodlightVariable -> m CustomFloodlightVariable #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CustomFloodlightVariable -> m CustomFloodlightVariable #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CustomFloodlightVariable -> m CustomFloodlightVariable #

Show CustomFloodlightVariable Source # 
Generic CustomFloodlightVariable Source # 
ToJSON CustomFloodlightVariable Source # 
FromJSON CustomFloodlightVariable Source # 
type Rep CustomFloodlightVariable Source # 
type Rep CustomFloodlightVariable = D1 (MetaData "CustomFloodlightVariable" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CustomFloodlightVariable'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cusKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_cusValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cusType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CustomFloodlightVariableType))))))

customFloodlightVariable :: CustomFloodlightVariable Source #

Creates a value of CustomFloodlightVariable with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cusKind :: Lens' CustomFloodlightVariable Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#customFloodlightVariable".

cusValue :: Lens' CustomFloodlightVariable (Maybe Text) Source #

The value of the custom floodlight variable. The length of string must not exceed 50 characters.

cusType :: Lens' CustomFloodlightVariable (Maybe CustomFloodlightVariableType) Source #

The type of custom floodlight variable to supply a value for. These map to the "u[1-20]=" in the tags.

CreativeRotationWeightCalculationStrategy

data CreativeRotationWeightCalculationStrategy Source #

Strategy for calculating weights. Used with CREATIVE_ROTATION_TYPE_RANDOM.

Constructors

WeightStrategyCustom
WEIGHT_STRATEGY_CUSTOM
WeightStrategyEqual
WEIGHT_STRATEGY_EQUAL
WeightStrategyHighestCtr
WEIGHT_STRATEGY_HIGHEST_CTR
WeightStrategyOptimized
WEIGHT_STRATEGY_OPTIMIZED

Instances

Enum CreativeRotationWeightCalculationStrategy Source # 
Eq CreativeRotationWeightCalculationStrategy Source # 
Data CreativeRotationWeightCalculationStrategy Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeRotationWeightCalculationStrategy -> c CreativeRotationWeightCalculationStrategy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeRotationWeightCalculationStrategy #

toConstr :: CreativeRotationWeightCalculationStrategy -> Constr #

dataTypeOf :: CreativeRotationWeightCalculationStrategy -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeRotationWeightCalculationStrategy) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeRotationWeightCalculationStrategy) #

gmapT :: (forall b. Data b => b -> b) -> CreativeRotationWeightCalculationStrategy -> CreativeRotationWeightCalculationStrategy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeRotationWeightCalculationStrategy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeRotationWeightCalculationStrategy -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeRotationWeightCalculationStrategy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeRotationWeightCalculationStrategy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeRotationWeightCalculationStrategy -> m CreativeRotationWeightCalculationStrategy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeRotationWeightCalculationStrategy -> m CreativeRotationWeightCalculationStrategy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeRotationWeightCalculationStrategy -> m CreativeRotationWeightCalculationStrategy #

Ord CreativeRotationWeightCalculationStrategy Source # 
Read CreativeRotationWeightCalculationStrategy Source # 
Show CreativeRotationWeightCalculationStrategy Source # 
Generic CreativeRotationWeightCalculationStrategy Source # 
Hashable CreativeRotationWeightCalculationStrategy Source # 
ToJSON CreativeRotationWeightCalculationStrategy Source # 
FromJSON CreativeRotationWeightCalculationStrategy Source # 
FromHttpApiData CreativeRotationWeightCalculationStrategy Source # 
ToHttpApiData CreativeRotationWeightCalculationStrategy Source # 
type Rep CreativeRotationWeightCalculationStrategy Source # 
type Rep CreativeRotationWeightCalculationStrategy = D1 (MetaData "CreativeRotationWeightCalculationStrategy" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "WeightStrategyCustom" PrefixI False) U1) (C1 (MetaCons "WeightStrategyEqual" PrefixI False) U1)) ((:+:) (C1 (MetaCons "WeightStrategyHighestCtr" PrefixI False) U1) (C1 (MetaCons "WeightStrategyOptimized" PrefixI False) U1)))

FilesListScope

data FilesListScope Source #

The scope that defines which results are returned, default is 'MINE'.

Constructors

FLSAll

ALL All files in account.

FLSMine

MINE My files.

FLSSharedWithMe

SHARED_WITH_ME Files shared with me.

Instances

Enum FilesListScope Source # 
Eq FilesListScope Source # 
Data FilesListScope Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FilesListScope -> c FilesListScope #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FilesListScope #

toConstr :: FilesListScope -> Constr #

dataTypeOf :: FilesListScope -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FilesListScope) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilesListScope) #

gmapT :: (forall b. Data b => b -> b) -> FilesListScope -> FilesListScope #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FilesListScope -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FilesListScope -> r #

gmapQ :: (forall d. Data d => d -> u) -> FilesListScope -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FilesListScope -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FilesListScope -> m FilesListScope #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FilesListScope -> m FilesListScope #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FilesListScope -> m FilesListScope #

Ord FilesListScope Source # 
Read FilesListScope Source # 
Show FilesListScope Source # 
Generic FilesListScope Source # 

Associated Types

type Rep FilesListScope :: * -> * #

Hashable FilesListScope Source # 
ToJSON FilesListScope Source # 
FromJSON FilesListScope Source # 
FromHttpApiData FilesListScope Source # 
ToHttpApiData FilesListScope Source # 
type Rep FilesListScope Source # 
type Rep FilesListScope = D1 (MetaData "FilesListScope" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "FLSAll" PrefixI False) U1) ((:+:) (C1 (MetaCons "FLSMine" PrefixI False) U1) (C1 (MetaCons "FLSSharedWithMe" PrefixI False) U1)))

ContentCategoriesListSortField

data ContentCategoriesListSortField Source #

Field by which to sort the list.

Constructors

CCLSFID
ID
CCLSFName
NAME

Instances

Enum ContentCategoriesListSortField Source # 
Eq ContentCategoriesListSortField Source # 
Data ContentCategoriesListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ContentCategoriesListSortField -> c ContentCategoriesListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ContentCategoriesListSortField #

toConstr :: ContentCategoriesListSortField -> Constr #

dataTypeOf :: ContentCategoriesListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ContentCategoriesListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ContentCategoriesListSortField) #

gmapT :: (forall b. Data b => b -> b) -> ContentCategoriesListSortField -> ContentCategoriesListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ContentCategoriesListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ContentCategoriesListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> ContentCategoriesListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ContentCategoriesListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ContentCategoriesListSortField -> m ContentCategoriesListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ContentCategoriesListSortField -> m ContentCategoriesListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ContentCategoriesListSortField -> m ContentCategoriesListSortField #

Ord ContentCategoriesListSortField Source # 
Read ContentCategoriesListSortField Source # 
Show ContentCategoriesListSortField Source # 
Generic ContentCategoriesListSortField Source # 
Hashable ContentCategoriesListSortField Source # 
ToJSON ContentCategoriesListSortField Source # 
FromJSON ContentCategoriesListSortField Source # 
FromHttpApiData ContentCategoriesListSortField Source # 
ToHttpApiData ContentCategoriesListSortField Source # 
type Rep ContentCategoriesListSortField Source # 
type Rep ContentCategoriesListSortField = D1 (MetaData "ContentCategoriesListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CCLSFID" PrefixI False) U1) (C1 (MetaCons "CCLSFName" PrefixI False) U1))

ProjectAudienceAgeGroup

data ProjectAudienceAgeGroup Source #

Audience age group of this project.

Constructors

PlanningAudienceAge1824
PLANNING_AUDIENCE_AGE_18_24
PlanningAudienceAge2534
PLANNING_AUDIENCE_AGE_25_34
PlanningAudienceAge3544
PLANNING_AUDIENCE_AGE_35_44
PlanningAudienceAge4554
PLANNING_AUDIENCE_AGE_45_54
PlanningAudienceAge5564
PLANNING_AUDIENCE_AGE_55_64
PlanningAudienceAge65OrMore
PLANNING_AUDIENCE_AGE_65_OR_MORE
PlanningAudienceAgeUnknown
PLANNING_AUDIENCE_AGE_UNKNOWN

Instances

Enum ProjectAudienceAgeGroup Source # 
Eq ProjectAudienceAgeGroup Source # 
Data ProjectAudienceAgeGroup Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProjectAudienceAgeGroup -> c ProjectAudienceAgeGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProjectAudienceAgeGroup #

toConstr :: ProjectAudienceAgeGroup -> Constr #

dataTypeOf :: ProjectAudienceAgeGroup -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProjectAudienceAgeGroup) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProjectAudienceAgeGroup) #

gmapT :: (forall b. Data b => b -> b) -> ProjectAudienceAgeGroup -> ProjectAudienceAgeGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProjectAudienceAgeGroup -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProjectAudienceAgeGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProjectAudienceAgeGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProjectAudienceAgeGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProjectAudienceAgeGroup -> m ProjectAudienceAgeGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProjectAudienceAgeGroup -> m ProjectAudienceAgeGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProjectAudienceAgeGroup -> m ProjectAudienceAgeGroup #

Ord ProjectAudienceAgeGroup Source # 
Read ProjectAudienceAgeGroup Source # 
Show ProjectAudienceAgeGroup Source # 
Generic ProjectAudienceAgeGroup Source # 
Hashable ProjectAudienceAgeGroup Source # 
ToJSON ProjectAudienceAgeGroup Source # 
FromJSON ProjectAudienceAgeGroup Source # 
FromHttpApiData ProjectAudienceAgeGroup Source # 
ToHttpApiData ProjectAudienceAgeGroup Source # 
type Rep ProjectAudienceAgeGroup Source # 
type Rep ProjectAudienceAgeGroup = D1 (MetaData "ProjectAudienceAgeGroup" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "PlanningAudienceAge1824" PrefixI False) U1) ((:+:) (C1 (MetaCons "PlanningAudienceAge2534" PrefixI False) U1) (C1 (MetaCons "PlanningAudienceAge3544" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PlanningAudienceAge4554" PrefixI False) U1) (C1 (MetaCons "PlanningAudienceAge5564" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PlanningAudienceAge65OrMore" PrefixI False) U1) (C1 (MetaCons "PlanningAudienceAgeUnknown" PrefixI False) U1))))

PlatformTypesListResponse

data PlatformTypesListResponse Source #

Platform Type List Response

See: platformTypesListResponse smart constructor.

Instances

Eq PlatformTypesListResponse Source # 
Data PlatformTypesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlatformTypesListResponse -> c PlatformTypesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlatformTypesListResponse #

toConstr :: PlatformTypesListResponse -> Constr #

dataTypeOf :: PlatformTypesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlatformTypesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlatformTypesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> PlatformTypesListResponse -> PlatformTypesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlatformTypesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlatformTypesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlatformTypesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlatformTypesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlatformTypesListResponse -> m PlatformTypesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlatformTypesListResponse -> m PlatformTypesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlatformTypesListResponse -> m PlatformTypesListResponse #

Show PlatformTypesListResponse Source # 
Generic PlatformTypesListResponse Source # 
ToJSON PlatformTypesListResponse Source # 
FromJSON PlatformTypesListResponse Source # 
type Rep PlatformTypesListResponse Source # 
type Rep PlatformTypesListResponse = D1 (MetaData "PlatformTypesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PlatformTypesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ptlrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_ptlrPlatformTypes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PlatformType])))))

platformTypesListResponse :: PlatformTypesListResponse Source #

Creates a value of PlatformTypesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ptlrKind :: Lens' PlatformTypesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#platformTypesListResponse".

AdType

data AdType Source #

Type of ad. This is a required field on insertion. Note that default ads (AD_SERVING_DEFAULT_AD) cannot be created directly (see Creative resource).

Constructors

ATAdServingClickTracker
AD_SERVING_CLICK_TRACKER
ATAdServingDefaultAd
AD_SERVING_DEFAULT_AD
ATAdServingStandardAd
AD_SERVING_STANDARD_AD
ATAdServingTracking
AD_SERVING_TRACKING

Instances

Enum AdType Source # 
Eq AdType Source # 

Methods

(==) :: AdType -> AdType -> Bool #

(/=) :: AdType -> AdType -> Bool #

Data AdType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdType -> c AdType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdType #

toConstr :: AdType -> Constr #

dataTypeOf :: AdType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdType) #

gmapT :: (forall b. Data b => b -> b) -> AdType -> AdType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdType -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdType -> m AdType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdType -> m AdType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdType -> m AdType #

Ord AdType Source # 
Read AdType Source # 
Show AdType Source # 
Generic AdType Source # 

Associated Types

type Rep AdType :: * -> * #

Methods

from :: AdType -> Rep AdType x #

to :: Rep AdType x -> AdType #

Hashable AdType Source # 

Methods

hashWithSalt :: Int -> AdType -> Int #

hash :: AdType -> Int #

ToJSON AdType Source # 
FromJSON AdType Source # 
FromHttpApiData AdType Source # 
ToHttpApiData AdType Source # 
type Rep AdType Source # 
type Rep AdType = D1 (MetaData "AdType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "ATAdServingClickTracker" PrefixI False) U1) (C1 (MetaCons "ATAdServingDefaultAd" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ATAdServingStandardAd" PrefixI False) U1) (C1 (MetaCons "ATAdServingTracking" PrefixI False) U1)))

LastModifiedInfo

data LastModifiedInfo Source #

Modification timestamp.

See: lastModifiedInfo smart constructor.

Instances

Eq LastModifiedInfo Source # 
Data LastModifiedInfo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LastModifiedInfo -> c LastModifiedInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LastModifiedInfo #

toConstr :: LastModifiedInfo -> Constr #

dataTypeOf :: LastModifiedInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LastModifiedInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LastModifiedInfo) #

gmapT :: (forall b. Data b => b -> b) -> LastModifiedInfo -> LastModifiedInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LastModifiedInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LastModifiedInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> LastModifiedInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LastModifiedInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LastModifiedInfo -> m LastModifiedInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LastModifiedInfo -> m LastModifiedInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LastModifiedInfo -> m LastModifiedInfo #

Show LastModifiedInfo Source # 
Generic LastModifiedInfo Source # 
ToJSON LastModifiedInfo Source # 
FromJSON LastModifiedInfo Source # 
type Rep LastModifiedInfo Source # 
type Rep LastModifiedInfo = D1 (MetaData "LastModifiedInfo" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" True) (C1 (MetaCons "LastModifiedInfo'" PrefixI True) (S1 (MetaSel (Just Symbol "_lmiTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Textual Int64)))))

lastModifiedInfo :: LastModifiedInfo Source #

Creates a value of LastModifiedInfo with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lmiTime :: Lens' LastModifiedInfo (Maybe Int64) Source #

Timestamp of the last change in milliseconds since epoch.

TargetWindow

data TargetWindow Source #

Target Window.

See: targetWindow smart constructor.

Instances

Eq TargetWindow Source # 
Data TargetWindow Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TargetWindow -> c TargetWindow #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TargetWindow #

toConstr :: TargetWindow -> Constr #

dataTypeOf :: TargetWindow -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TargetWindow) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TargetWindow) #

gmapT :: (forall b. Data b => b -> b) -> TargetWindow -> TargetWindow #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TargetWindow -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TargetWindow -> r #

gmapQ :: (forall d. Data d => d -> u) -> TargetWindow -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TargetWindow -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TargetWindow -> m TargetWindow #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetWindow -> m TargetWindow #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetWindow -> m TargetWindow #

Show TargetWindow Source # 
Generic TargetWindow Source # 

Associated Types

type Rep TargetWindow :: * -> * #

ToJSON TargetWindow Source # 
FromJSON TargetWindow Source # 
type Rep TargetWindow Source # 
type Rep TargetWindow = D1 (MetaData "TargetWindow" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "TargetWindow'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_twCustomHTML") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_twTargetWindowOption") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TargetWindowTargetWindowOption)))))

targetWindow :: TargetWindow Source #

Creates a value of TargetWindow with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

twCustomHTML :: Lens' TargetWindow (Maybe Text) Source #

User-entered value.

twTargetWindowOption :: Lens' TargetWindow (Maybe TargetWindowTargetWindowOption) Source #

Type of browser window for which the backup image of the flash creative can be displayed.

ChangeLogsListAction

data ChangeLogsListAction Source #

Select only change logs with the specified action.

Constructors

ActionAdd
ACTION_ADD
ActionAssign
ACTION_ASSIGN
ActionAssociate
ACTION_ASSOCIATE
ActionCreate
ACTION_CREATE
ActionDelete
ACTION_DELETE
ActionDisable
ACTION_DISABLE
ActionEmailTags
ACTION_EMAIL_TAGS
ActionEnable
ACTION_ENABLE
ActionLink
ACTION_LINK
ActionMarkAsDefault
ACTION_MARK_AS_DEFAULT
ActionPush
ACTION_PUSH
ActionRemove
ACTION_REMOVE
ActionSend
ACTION_SEND
ActionShare
ACTION_SHARE
ActionUnassign
ACTION_UNASSIGN
ActionUnlink
ACTION_UNLINK
ActionUpdate
ACTION_UPDATE

Instances

Enum ChangeLogsListAction Source # 
Eq ChangeLogsListAction Source # 
Data ChangeLogsListAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChangeLogsListAction -> c ChangeLogsListAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChangeLogsListAction #

toConstr :: ChangeLogsListAction -> Constr #

dataTypeOf :: ChangeLogsListAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChangeLogsListAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChangeLogsListAction) #

gmapT :: (forall b. Data b => b -> b) -> ChangeLogsListAction -> ChangeLogsListAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChangeLogsListAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChangeLogsListAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChangeLogsListAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChangeLogsListAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChangeLogsListAction -> m ChangeLogsListAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeLogsListAction -> m ChangeLogsListAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeLogsListAction -> m ChangeLogsListAction #

Ord ChangeLogsListAction Source # 
Read ChangeLogsListAction Source # 
Show ChangeLogsListAction Source # 
Generic ChangeLogsListAction Source # 
Hashable ChangeLogsListAction Source # 
ToJSON ChangeLogsListAction Source # 
FromJSON ChangeLogsListAction Source # 
FromHttpApiData ChangeLogsListAction Source # 
ToHttpApiData ChangeLogsListAction Source # 
type Rep ChangeLogsListAction Source # 
type Rep ChangeLogsListAction = D1 (MetaData "ChangeLogsListAction" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ActionAdd" PrefixI False) U1) (C1 (MetaCons "ActionAssign" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ActionAssociate" PrefixI False) U1) (C1 (MetaCons "ActionCreate" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "ActionDelete" PrefixI False) U1) (C1 (MetaCons "ActionDisable" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ActionEmailTags" PrefixI False) U1) (C1 (MetaCons "ActionEnable" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ActionLink" PrefixI False) U1) (C1 (MetaCons "ActionMarkAsDefault" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ActionPush" PrefixI False) U1) (C1 (MetaCons "ActionRemove" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "ActionSend" PrefixI False) U1) (C1 (MetaCons "ActionShare" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ActionUnassign" PrefixI False) U1) ((:+:) (C1 (MetaCons "ActionUnlink" PrefixI False) U1) (C1 (MetaCons "ActionUpdate" PrefixI False) U1))))))

CreativeArtworkType

data CreativeArtworkType Source #

Type of artwork used for the creative. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA, and all VPAID.

Constructors

CATArtworkTypeFlash
ARTWORK_TYPE_FLASH
CATArtworkTypeHTML5
ARTWORK_TYPE_HTML5
CATArtworkTypeImage
ARTWORK_TYPE_IMAGE
CATArtworkTypeMixed
ARTWORK_TYPE_MIXED

Instances

Enum CreativeArtworkType Source # 
Eq CreativeArtworkType Source # 
Data CreativeArtworkType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeArtworkType -> c CreativeArtworkType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeArtworkType #

toConstr :: CreativeArtworkType -> Constr #

dataTypeOf :: CreativeArtworkType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeArtworkType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeArtworkType) #

gmapT :: (forall b. Data b => b -> b) -> CreativeArtworkType -> CreativeArtworkType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeArtworkType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeArtworkType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeArtworkType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeArtworkType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeArtworkType -> m CreativeArtworkType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeArtworkType -> m CreativeArtworkType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeArtworkType -> m CreativeArtworkType #

Ord CreativeArtworkType Source # 
Read CreativeArtworkType Source # 
Show CreativeArtworkType Source # 
Generic CreativeArtworkType Source # 
Hashable CreativeArtworkType Source # 
ToJSON CreativeArtworkType Source # 
FromJSON CreativeArtworkType Source # 
FromHttpApiData CreativeArtworkType Source # 
ToHttpApiData CreativeArtworkType Source # 
type Rep CreativeArtworkType Source # 
type Rep CreativeArtworkType = D1 (MetaData "CreativeArtworkType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "CATArtworkTypeFlash" PrefixI False) U1) (C1 (MetaCons "CATArtworkTypeHTML5" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CATArtworkTypeImage" PrefixI False) U1) (C1 (MetaCons "CATArtworkTypeMixed" PrefixI False) U1)))

PlacementStatus

data PlacementStatus Source #

Third-party placement status.

Constructors

AcknowledgeAcceptance
ACKNOWLEDGE_ACCEPTANCE
AcknowledgeRejection
ACKNOWLEDGE_REJECTION
Draft
DRAFT
PaymentAccepted
PAYMENT_ACCEPTED
PaymentRejected
PAYMENT_REJECTED
PendingReview
PENDING_REVIEW

Instances

Enum PlacementStatus Source # 
Eq PlacementStatus Source # 
Data PlacementStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementStatus -> c PlacementStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementStatus #

toConstr :: PlacementStatus -> Constr #

dataTypeOf :: PlacementStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementStatus) #

gmapT :: (forall b. Data b => b -> b) -> PlacementStatus -> PlacementStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementStatus -> m PlacementStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementStatus -> m PlacementStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementStatus -> m PlacementStatus #

Ord PlacementStatus Source # 
Read PlacementStatus Source # 
Show PlacementStatus Source # 
Generic PlacementStatus Source # 
Hashable PlacementStatus Source # 
ToJSON PlacementStatus Source # 
FromJSON PlacementStatus Source # 
FromHttpApiData PlacementStatus Source # 
ToHttpApiData PlacementStatus Source # 
type Rep PlacementStatus Source # 
type Rep PlacementStatus = D1 (MetaData "PlacementStatus" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "AcknowledgeAcceptance" PrefixI False) U1) ((:+:) (C1 (MetaCons "AcknowledgeRejection" PrefixI False) U1) (C1 (MetaCons "Draft" PrefixI False) U1))) ((:+:) (C1 (MetaCons "PaymentAccepted" PrefixI False) U1) ((:+:) (C1 (MetaCons "PaymentRejected" PrefixI False) U1) (C1 (MetaCons "PendingReview" PrefixI False) U1))))

AccountPermissionGroup

data AccountPermissionGroup Source #

AccountPermissionGroups contains a mapping of permission group IDs to names. A permission group is a grouping of account permissions.

See: accountPermissionGroup smart constructor.

Instances

Eq AccountPermissionGroup Source # 
Data AccountPermissionGroup Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountPermissionGroup -> c AccountPermissionGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountPermissionGroup #

toConstr :: AccountPermissionGroup -> Constr #

dataTypeOf :: AccountPermissionGroup -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountPermissionGroup) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountPermissionGroup) #

gmapT :: (forall b. Data b => b -> b) -> AccountPermissionGroup -> AccountPermissionGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountPermissionGroup -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountPermissionGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountPermissionGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountPermissionGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountPermissionGroup -> m AccountPermissionGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountPermissionGroup -> m AccountPermissionGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountPermissionGroup -> m AccountPermissionGroup #

Show AccountPermissionGroup Source # 
Generic AccountPermissionGroup Source # 
ToJSON AccountPermissionGroup Source # 
FromJSON AccountPermissionGroup Source # 
type Rep AccountPermissionGroup Source # 
type Rep AccountPermissionGroup = D1 (MetaData "AccountPermissionGroup" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AccountPermissionGroup'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_apgpKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_apgpName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_apgpId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

accountPermissionGroup :: AccountPermissionGroup Source #

Creates a value of AccountPermissionGroup with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

apgpKind :: Lens' AccountPermissionGroup Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#accountPermissionGroup".

apgpName :: Lens' AccountPermissionGroup (Maybe Text) Source #

Name of this account permission group.

apgpId :: Lens' AccountPermissionGroup (Maybe Int64) Source #

ID of this account permission group.

Advertiser

data Advertiser Source #

Contains properties of a DCM advertiser.

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.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Advertiser'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_advdOriginalFloodlightConfigurationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_advdStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AdvertiserStatus))) (S1 (MetaSel (Just Symbol "_advdFloodlightConfigurationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_advdKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_advdSuspended") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_advdIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_advdAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_advdDefaultEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_advdName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_advdAdvertiserGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_advdDefaultClickThroughEventTagId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_advdId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_advdSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_advdFloodlightConfigurationIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_advdClickThroughURLSuffix") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

advdOriginalFloodlightConfigurationId :: Lens' Advertiser (Maybe Int64) Source #

Original floodlight configuration before any sharing occurred. Set the floodlightConfigurationId of this advertiser to originalFloodlightConfigurationId to unshare the advertiser's current floodlight configuration. You cannot unshare an advertiser's floodlight configuration if the shared configuration has activities associated with any campaign or placement.

advdStatus :: Lens' Advertiser (Maybe AdvertiserStatus) Source #

Status of this advertiser.

advdFloodlightConfigurationId :: Lens' Advertiser (Maybe Int64) Source #

Floodlight configuration ID of this advertiser. The floodlight configuration ID will be created automatically, so on insert this field should be left blank. This field can be set to another advertiser's floodlight configuration ID in order to share that advertiser's floodlight configuration with this advertiser, so long as: - This advertiser's original floodlight configuration is not already associated with floodlight activities or floodlight activity groups. - This advertiser's original floodlight configuration is not already shared with another advertiser.

advdKind :: Lens' Advertiser Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#advertiser".

advdSuspended :: Lens' Advertiser (Maybe Bool) Source #

Suspension status of this advertiser.

advdIdDimensionValue :: Lens' Advertiser (Maybe DimensionValue) Source #

Dimension value for the ID of this advertiser. This is a read-only, auto-generated field.

advdAccountId :: Lens' Advertiser (Maybe Int64) Source #

Account ID of this advertiser.This is a read-only field that can be left blank.

advdDefaultEmail :: Lens' Advertiser (Maybe Text) Source #

Default email address used in sender field for tag emails.

advdName :: Lens' Advertiser (Maybe Text) Source #

Name of this advertiser. This is a required field and must be less than 256 characters long and unique among advertisers of the same account.

advdAdvertiserGroupId :: Lens' Advertiser (Maybe Int64) Source #

ID of the advertiser group this advertiser belongs to. You can group advertisers for reporting purposes, allowing you to see aggregated information for all advertisers in each group.

advdDefaultClickThroughEventTagId :: Lens' Advertiser (Maybe Int64) Source #

ID of the click-through event tag to apply by default to the landing pages of this advertiser's campaigns.

advdId :: Lens' Advertiser (Maybe Int64) Source #

ID of this advertiser. This is a read-only, auto-generated field.

advdSubAccountId :: Lens' Advertiser (Maybe Int64) Source #

Subaccount ID of this advertiser.This is a read-only field that can be left blank.

advdFloodlightConfigurationIdDimensionValue :: Lens' Advertiser (Maybe DimensionValue) Source #

Dimension value for the ID of the floodlight configuration. This is a read-only, auto-generated field.

advdClickThroughURLSuffix :: Lens' Advertiser (Maybe Text) Source #

Suffix added to click-through URL of ad creative associations under this advertiser. Must be less than 129 characters long.

ReportScheduleRunsOnDayOfMonth

data ReportScheduleRunsOnDayOfMonth Source #

Enum to define for "MONTHLY" scheduled reports whether reports should be repeated on the same day of the month as "startDate" or the same day of the week of the month. Example: If 'startDate' is Monday, April 2nd 2012 (2012-04-02), "DAY_OF_MONTH" would run subsequent reports on the 2nd of every Month, and "WEEK_OF_MONTH" would run subsequent reports on the first Monday of the month.

Constructors

DayOfMonth
DAY_OF_MONTH
WeekOfMonth
WEEK_OF_MONTH

Instances

Enum ReportScheduleRunsOnDayOfMonth Source # 
Eq ReportScheduleRunsOnDayOfMonth Source # 
Data ReportScheduleRunsOnDayOfMonth Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportScheduleRunsOnDayOfMonth -> c ReportScheduleRunsOnDayOfMonth #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportScheduleRunsOnDayOfMonth #

toConstr :: ReportScheduleRunsOnDayOfMonth -> Constr #

dataTypeOf :: ReportScheduleRunsOnDayOfMonth -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportScheduleRunsOnDayOfMonth) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportScheduleRunsOnDayOfMonth) #

gmapT :: (forall b. Data b => b -> b) -> ReportScheduleRunsOnDayOfMonth -> ReportScheduleRunsOnDayOfMonth #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportScheduleRunsOnDayOfMonth -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportScheduleRunsOnDayOfMonth -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportScheduleRunsOnDayOfMonth -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportScheduleRunsOnDayOfMonth -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportScheduleRunsOnDayOfMonth -> m ReportScheduleRunsOnDayOfMonth #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportScheduleRunsOnDayOfMonth -> m ReportScheduleRunsOnDayOfMonth #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportScheduleRunsOnDayOfMonth -> m ReportScheduleRunsOnDayOfMonth #

Ord ReportScheduleRunsOnDayOfMonth Source # 
Read ReportScheduleRunsOnDayOfMonth Source # 
Show ReportScheduleRunsOnDayOfMonth Source # 
Generic ReportScheduleRunsOnDayOfMonth Source # 
Hashable ReportScheduleRunsOnDayOfMonth Source # 
ToJSON ReportScheduleRunsOnDayOfMonth Source # 
FromJSON ReportScheduleRunsOnDayOfMonth Source # 
FromHttpApiData ReportScheduleRunsOnDayOfMonth Source # 
ToHttpApiData ReportScheduleRunsOnDayOfMonth Source # 
type Rep ReportScheduleRunsOnDayOfMonth Source # 
type Rep ReportScheduleRunsOnDayOfMonth = D1 (MetaData "ReportScheduleRunsOnDayOfMonth" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "DayOfMonth" PrefixI False) U1) (C1 (MetaCons "WeekOfMonth" PrefixI False) U1))

UserRole

data UserRole Source #

Contains properties of auser role, which is used to manage user access.

See: userRole smart constructor.

Instances

Eq UserRole Source # 
Data UserRole Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserRole -> c UserRole #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserRole #

toConstr :: UserRole -> Constr #

dataTypeOf :: UserRole -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserRole) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserRole) #

gmapT :: (forall b. Data b => b -> b) -> UserRole -> UserRole #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserRole -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserRole -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserRole -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserRole -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserRole -> m UserRole #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRole -> m UserRole #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRole -> m UserRole #

Show UserRole Source # 
Generic UserRole Source # 

Associated Types

type Rep UserRole :: * -> * #

Methods

from :: UserRole -> Rep UserRole x #

to :: Rep UserRole x -> UserRole #

ToJSON UserRole Source # 
FromJSON UserRole Source # 
type Rep UserRole Source # 

userRole :: UserRole Source #

Creates a value of UserRole with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

urParentUserRoleId :: Lens' UserRole (Maybe Int64) Source #

ID of the user role that this user role is based on or copied from. This is a required field.

urKind :: Lens' UserRole Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#userRole".

urDefaultUserRole :: Lens' UserRole (Maybe Bool) Source #

Whether this is a default user role. Default user roles are created by the system for the account/subaccount and cannot be modified or deleted. Each default user role comes with a basic set of preassigned permissions.

urAccountId :: Lens' UserRole (Maybe Int64) Source #

Account ID of this user role. This is a read-only field that can be left blank.

urName :: Lens' UserRole (Maybe Text) Source #

Name of this user role. This is a required field. Must be less than 256 characters long. If this user role is under a subaccount, the name must be unique among sites of the same subaccount. Otherwise, this user role is a top-level user role, and the name must be unique among top-level user roles of the same account.

urId :: Lens' UserRole (Maybe Int64) Source #

ID of this user role. This is a read-only, auto-generated field.

urPermissions :: Lens' UserRole [UserRolePermission] Source #

List of permissions associated with this user role.

urSubAccountId :: Lens' UserRole (Maybe Int64) Source #

Subaccount ID of this user role. This is a read-only field that can be left blank.

FloodlightActivityUserDefinedVariableTypesItem

data FloodlightActivityUserDefinedVariableTypesItem Source #

Instances

Enum FloodlightActivityUserDefinedVariableTypesItem Source # 
Eq FloodlightActivityUserDefinedVariableTypesItem Source # 
Data FloodlightActivityUserDefinedVariableTypesItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivityUserDefinedVariableTypesItem -> c FloodlightActivityUserDefinedVariableTypesItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivityUserDefinedVariableTypesItem #

toConstr :: FloodlightActivityUserDefinedVariableTypesItem -> Constr #

dataTypeOf :: FloodlightActivityUserDefinedVariableTypesItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivityUserDefinedVariableTypesItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivityUserDefinedVariableTypesItem) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivityUserDefinedVariableTypesItem -> FloodlightActivityUserDefinedVariableTypesItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityUserDefinedVariableTypesItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityUserDefinedVariableTypesItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivityUserDefinedVariableTypesItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivityUserDefinedVariableTypesItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivityUserDefinedVariableTypesItem -> m FloodlightActivityUserDefinedVariableTypesItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityUserDefinedVariableTypesItem -> m FloodlightActivityUserDefinedVariableTypesItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityUserDefinedVariableTypesItem -> m FloodlightActivityUserDefinedVariableTypesItem #

Ord FloodlightActivityUserDefinedVariableTypesItem Source # 
Read FloodlightActivityUserDefinedVariableTypesItem Source # 
Show FloodlightActivityUserDefinedVariableTypesItem Source # 
Generic FloodlightActivityUserDefinedVariableTypesItem Source # 
Hashable FloodlightActivityUserDefinedVariableTypesItem Source # 
ToJSON FloodlightActivityUserDefinedVariableTypesItem Source # 
FromJSON FloodlightActivityUserDefinedVariableTypesItem Source # 
FromHttpApiData FloodlightActivityUserDefinedVariableTypesItem Source # 
ToHttpApiData FloodlightActivityUserDefinedVariableTypesItem Source # 
type Rep FloodlightActivityUserDefinedVariableTypesItem Source # 
type Rep FloodlightActivityUserDefinedVariableTypesItem = D1 (MetaData "FloodlightActivityUserDefinedVariableTypesItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "FAUDVTIU1" PrefixI False) U1) (C1 (MetaCons "FAUDVTIU10" PrefixI False) U1)) ((:+:) (C1 (MetaCons "FAUDVTIU11" PrefixI False) U1) ((:+:) (C1 (MetaCons "FAUDVTIU12" PrefixI False) U1) (C1 (MetaCons "FAUDVTIU13" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "FAUDVTIU14" PrefixI False) U1) (C1 (MetaCons "FAUDVTIU15" PrefixI False) U1)) ((:+:) (C1 (MetaCons "FAUDVTIU16" PrefixI False) U1) ((:+:) (C1 (MetaCons "FAUDVTIU17" PrefixI False) U1) (C1 (MetaCons "FAUDVTIU18" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "FAUDVTIU19" PrefixI False) U1) (C1 (MetaCons "FAUDVTIU2" PrefixI False) U1)) ((:+:) (C1 (MetaCons "FAUDVTIU20" PrefixI False) U1) ((:+:) (C1 (MetaCons "FAUDVTIU3" PrefixI False) U1) (C1 (MetaCons "FAUDVTIU4" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "FAUDVTIU5" PrefixI False) U1) (C1 (MetaCons "FAUDVTIU6" PrefixI False) U1)) ((:+:) (C1 (MetaCons "FAUDVTIU7" PrefixI False) U1) ((:+:) (C1 (MetaCons "FAUDVTIU8" PrefixI False) U1) (C1 (MetaCons "FAUDVTIU9" PrefixI False) U1))))))

EventTagSiteFilterType

data EventTagSiteFilterType Source #

Site filter type for this event tag. If no type is specified then the event tag will be applied to all sites.

Constructors

BlackList
BLACKLIST
WhiteList
WHITELIST

Instances

Enum EventTagSiteFilterType Source # 
Eq EventTagSiteFilterType Source # 
Data EventTagSiteFilterType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventTagSiteFilterType -> c EventTagSiteFilterType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventTagSiteFilterType #

toConstr :: EventTagSiteFilterType -> Constr #

dataTypeOf :: EventTagSiteFilterType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EventTagSiteFilterType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventTagSiteFilterType) #

gmapT :: (forall b. Data b => b -> b) -> EventTagSiteFilterType -> EventTagSiteFilterType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventTagSiteFilterType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventTagSiteFilterType -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventTagSiteFilterType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventTagSiteFilterType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventTagSiteFilterType -> m EventTagSiteFilterType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTagSiteFilterType -> m EventTagSiteFilterType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTagSiteFilterType -> m EventTagSiteFilterType #

Ord EventTagSiteFilterType Source # 
Read EventTagSiteFilterType Source # 
Show EventTagSiteFilterType Source # 
Generic EventTagSiteFilterType Source # 
Hashable EventTagSiteFilterType Source # 
ToJSON EventTagSiteFilterType Source # 
FromJSON EventTagSiteFilterType Source # 
FromHttpApiData EventTagSiteFilterType Source # 
ToHttpApiData EventTagSiteFilterType Source # 
type Rep EventTagSiteFilterType Source # 
type Rep EventTagSiteFilterType = D1 (MetaData "EventTagSiteFilterType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "BlackList" PrefixI False) U1) (C1 (MetaCons "WhiteList" PrefixI False) U1))

ReportFormat

data ReportFormat Source #

The output format of the report. If not specified, default format is "CSV". Note that the actual format in the completed report file might differ if for instance the report's size exceeds the format's capabilities. "CSV" will then be the fallback format.

Constructors

RFCSV
CSV
RFExcel
EXCEL

Instances

Enum ReportFormat Source # 
Eq ReportFormat Source # 
Data ReportFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportFormat -> c ReportFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportFormat #

toConstr :: ReportFormat -> Constr #

dataTypeOf :: ReportFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportFormat) #

gmapT :: (forall b. Data b => b -> b) -> ReportFormat -> ReportFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportFormat -> m ReportFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportFormat -> m ReportFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportFormat -> m ReportFormat #

Ord ReportFormat Source # 
Read ReportFormat Source # 
Show ReportFormat Source # 
Generic ReportFormat Source # 

Associated Types

type Rep ReportFormat :: * -> * #

Hashable ReportFormat Source # 
ToJSON ReportFormat Source # 
FromJSON ReportFormat Source # 
FromHttpApiData ReportFormat Source # 
ToHttpApiData ReportFormat Source # 
type Rep ReportFormat Source # 
type Rep ReportFormat = D1 (MetaData "ReportFormat" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "RFCSV" PrefixI False) U1) (C1 (MetaCons "RFExcel" PrefixI False) U1))

PlacementGroupPlacementGroupType

data PlacementGroupPlacementGroupType Source #

Type of this placement group. A package is a simple group of placements that acts as a single pricing point for a group of tags. A roadblock is a group of placements that not only acts as a single pricing point, but also assumes that all the tags in it will be served at the same time. A roadblock requires one of its assigned placements to be marked as primary for reporting. This field is required on insertion.

Constructors

PGPGTPlacementPackage
PLACEMENT_PACKAGE
PGPGTPlacementRoadblock
PLACEMENT_ROADBLOCK

Instances

Enum PlacementGroupPlacementGroupType Source # 
Eq PlacementGroupPlacementGroupType Source # 
Data PlacementGroupPlacementGroupType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementGroupPlacementGroupType -> c PlacementGroupPlacementGroupType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementGroupPlacementGroupType #

toConstr :: PlacementGroupPlacementGroupType -> Constr #

dataTypeOf :: PlacementGroupPlacementGroupType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementGroupPlacementGroupType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementGroupPlacementGroupType) #

gmapT :: (forall b. Data b => b -> b) -> PlacementGroupPlacementGroupType -> PlacementGroupPlacementGroupType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroupPlacementGroupType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroupPlacementGroupType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementGroupPlacementGroupType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementGroupPlacementGroupType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementGroupPlacementGroupType -> m PlacementGroupPlacementGroupType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroupPlacementGroupType -> m PlacementGroupPlacementGroupType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroupPlacementGroupType -> m PlacementGroupPlacementGroupType #

Ord PlacementGroupPlacementGroupType Source # 
Read PlacementGroupPlacementGroupType Source # 
Show PlacementGroupPlacementGroupType Source # 
Generic PlacementGroupPlacementGroupType Source # 
Hashable PlacementGroupPlacementGroupType Source # 
ToJSON PlacementGroupPlacementGroupType Source # 
FromJSON PlacementGroupPlacementGroupType Source # 
FromHttpApiData PlacementGroupPlacementGroupType Source # 
ToHttpApiData PlacementGroupPlacementGroupType Source # 
type Rep PlacementGroupPlacementGroupType Source # 
type Rep PlacementGroupPlacementGroupType = D1 (MetaData "PlacementGroupPlacementGroupType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PGPGTPlacementPackage" PrefixI False) U1) (C1 (MetaCons "PGPGTPlacementRoadblock" PrefixI False) U1))

DirectorySitesListResponse

data DirectorySitesListResponse Source #

Directory Site List Response

See: directorySitesListResponse smart constructor.

Instances

Eq DirectorySitesListResponse Source # 
Data DirectorySitesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectorySitesListResponse -> c DirectorySitesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectorySitesListResponse #

toConstr :: DirectorySitesListResponse -> Constr #

dataTypeOf :: DirectorySitesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectorySitesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectorySitesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> DirectorySitesListResponse -> DirectorySitesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySitesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySitesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectorySitesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectorySitesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectorySitesListResponse -> m DirectorySitesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySitesListResponse -> m DirectorySitesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySitesListResponse -> m DirectorySitesListResponse #

Show DirectorySitesListResponse Source # 
Generic DirectorySitesListResponse Source # 
ToJSON DirectorySitesListResponse Source # 
FromJSON DirectorySitesListResponse Source # 
type Rep DirectorySitesListResponse Source # 
type Rep DirectorySitesListResponse = D1 (MetaData "DirectorySitesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DirectorySitesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dslrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_dslrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_dslrDirectorySites") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DirectorySite]))))))

directorySitesListResponse :: DirectorySitesListResponse Source #

Creates a value of DirectorySitesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dslrNextPageToken :: Lens' DirectorySitesListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

dslrKind :: Lens' DirectorySitesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#directorySitesListResponse".

ConversionError

data ConversionError Source #

The error code and description for a conversion that failed to insert.

See: conversionError smart constructor.

Instances

Eq ConversionError Source # 
Data ConversionError Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConversionError -> c ConversionError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConversionError #

toConstr :: ConversionError -> Constr #

dataTypeOf :: ConversionError -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConversionError) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConversionError) #

gmapT :: (forall b. Data b => b -> b) -> ConversionError -> ConversionError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConversionError -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConversionError -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConversionError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConversionError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConversionError -> m ConversionError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConversionError -> m ConversionError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConversionError -> m ConversionError #

Show ConversionError Source # 
Generic ConversionError Source # 
ToJSON ConversionError Source # 
FromJSON ConversionError Source # 
type Rep ConversionError Source # 
type Rep ConversionError = D1 (MetaData "ConversionError" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ConversionError'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ceKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_ceCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ConversionErrorCode))) (S1 (MetaSel (Just Symbol "_ceMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

conversionError :: ConversionError Source #

Creates a value of ConversionError with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ceKind :: Lens' ConversionError Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#conversionError".

ceMessage :: Lens' ConversionError (Maybe Text) Source #

A description of the error.

PricingPricingType

data PricingPricingType Source #

Pricing type of this inventory item.

Constructors

PlanningPlacementPricingTypeClicks
PLANNING_PLACEMENT_PRICING_TYPE_CLICKS
PlanningPlacementPricingTypeCpa
PLANNING_PLACEMENT_PRICING_TYPE_CPA
PlanningPlacementPricingTypeCpc
PLANNING_PLACEMENT_PRICING_TYPE_CPC
PlanningPlacementPricingTypeCpm
PLANNING_PLACEMENT_PRICING_TYPE_CPM
PlanningPlacementPricingTypeFlatRateClicks
PLANNING_PLACEMENT_PRICING_TYPE_FLAT_RATE_CLICKS
PlanningPlacementPricingTypeFlatRateImpressions
PLANNING_PLACEMENT_PRICING_TYPE_FLAT_RATE_IMPRESSIONS
PlanningPlacementPricingTypeImpressions
PLANNING_PLACEMENT_PRICING_TYPE_IMPRESSIONS

Instances

Enum PricingPricingType Source # 
Eq PricingPricingType Source # 
Data PricingPricingType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PricingPricingType -> c PricingPricingType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PricingPricingType #

toConstr :: PricingPricingType -> Constr #

dataTypeOf :: PricingPricingType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PricingPricingType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PricingPricingType) #

gmapT :: (forall b. Data b => b -> b) -> PricingPricingType -> PricingPricingType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PricingPricingType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PricingPricingType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PricingPricingType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PricingPricingType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PricingPricingType -> m PricingPricingType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PricingPricingType -> m PricingPricingType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PricingPricingType -> m PricingPricingType #

Ord PricingPricingType Source # 
Read PricingPricingType Source # 
Show PricingPricingType Source # 
Generic PricingPricingType Source # 
Hashable PricingPricingType Source # 
ToJSON PricingPricingType Source # 
FromJSON PricingPricingType Source # 
FromHttpApiData PricingPricingType Source # 
ToHttpApiData PricingPricingType Source # 
type Rep PricingPricingType Source # 
type Rep PricingPricingType = D1 (MetaData "PricingPricingType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "PlanningPlacementPricingTypeClicks" PrefixI False) U1) ((:+:) (C1 (MetaCons "PlanningPlacementPricingTypeCpa" PrefixI False) U1) (C1 (MetaCons "PlanningPlacementPricingTypeCpc" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PlanningPlacementPricingTypeCpm" PrefixI False) U1) (C1 (MetaCons "PlanningPlacementPricingTypeFlatRateClicks" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PlanningPlacementPricingTypeFlatRateImpressions" PrefixI False) U1) (C1 (MetaCons "PlanningPlacementPricingTypeImpressions" PrefixI False) U1))))

PricingSchedulePricingPeriod

data PricingSchedulePricingPeriod Source #

Pricing Period

See: pricingSchedulePricingPeriod smart constructor.

Instances

Eq PricingSchedulePricingPeriod Source # 
Data PricingSchedulePricingPeriod Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PricingSchedulePricingPeriod -> c PricingSchedulePricingPeriod #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PricingSchedulePricingPeriod #

toConstr :: PricingSchedulePricingPeriod -> Constr #

dataTypeOf :: PricingSchedulePricingPeriod -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PricingSchedulePricingPeriod) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PricingSchedulePricingPeriod) #

gmapT :: (forall b. Data b => b -> b) -> PricingSchedulePricingPeriod -> PricingSchedulePricingPeriod #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PricingSchedulePricingPeriod -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PricingSchedulePricingPeriod -> r #

gmapQ :: (forall d. Data d => d -> u) -> PricingSchedulePricingPeriod -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PricingSchedulePricingPeriod -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PricingSchedulePricingPeriod -> m PricingSchedulePricingPeriod #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PricingSchedulePricingPeriod -> m PricingSchedulePricingPeriod #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PricingSchedulePricingPeriod -> m PricingSchedulePricingPeriod #

Show PricingSchedulePricingPeriod Source # 
Generic PricingSchedulePricingPeriod Source # 
ToJSON PricingSchedulePricingPeriod Source # 
FromJSON PricingSchedulePricingPeriod Source # 
type Rep PricingSchedulePricingPeriod Source # 
type Rep PricingSchedulePricingPeriod = D1 (MetaData "PricingSchedulePricingPeriod" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PricingSchedulePricingPeriod'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_psppEndDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date'))) (S1 (MetaSel (Just Symbol "_psppRateOrCostNanos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_psppStartDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date'))) ((:*:) (S1 (MetaSel (Just Symbol "_psppUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_psppPricingComment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

pricingSchedulePricingPeriod :: PricingSchedulePricingPeriod Source #

Creates a value of PricingSchedulePricingPeriod with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

psppEndDate :: Lens' PricingSchedulePricingPeriod (Maybe Day) Source #

Pricing period end date. This date must be later than, or the same day as, the pricing period start date, but not later than the placement end date. The period end date can be the same date as the period start date. If, for example, you set 6/25/2015 as both the start and end dates, the effective pricing period date is just that day only, 6/25/2015. The hours, minutes, and seconds of the end date should not be set, as doing so will result in an error.

psppRateOrCostNanos :: Lens' PricingSchedulePricingPeriod (Maybe Int64) Source #

Rate or cost of this pricing period.

psppStartDate :: Lens' PricingSchedulePricingPeriod (Maybe Day) Source #

Pricing period start date. This date must be later than, or the same day as, the placement start date. The hours, minutes, and seconds of the start date should not be set, as doing so will result in an error.

psppUnits :: Lens' PricingSchedulePricingPeriod (Maybe Int64) Source #

Units of this pricing period.

SubAccountsListSortOrder

data SubAccountsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

SALSOAscending
ASCENDING
SALSODescending
DESCENDING

Instances

Enum SubAccountsListSortOrder Source # 
Eq SubAccountsListSortOrder Source # 
Data SubAccountsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SubAccountsListSortOrder -> c SubAccountsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SubAccountsListSortOrder #

toConstr :: SubAccountsListSortOrder -> Constr #

dataTypeOf :: SubAccountsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SubAccountsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SubAccountsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> SubAccountsListSortOrder -> SubAccountsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SubAccountsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SubAccountsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> SubAccountsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SubAccountsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SubAccountsListSortOrder -> m SubAccountsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SubAccountsListSortOrder -> m SubAccountsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SubAccountsListSortOrder -> m SubAccountsListSortOrder #

Ord SubAccountsListSortOrder Source # 
Read SubAccountsListSortOrder Source # 
Show SubAccountsListSortOrder Source # 
Generic SubAccountsListSortOrder Source # 
Hashable SubAccountsListSortOrder Source # 
ToJSON SubAccountsListSortOrder Source # 
FromJSON SubAccountsListSortOrder Source # 
FromHttpApiData SubAccountsListSortOrder Source # 
ToHttpApiData SubAccountsListSortOrder Source # 
type Rep SubAccountsListSortOrder Source # 
type Rep SubAccountsListSortOrder = D1 (MetaData "SubAccountsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "SALSOAscending" PrefixI False) U1) (C1 (MetaCons "SALSODescending" PrefixI False) U1))

DirectorySiteContactsListResponse

data DirectorySiteContactsListResponse Source #

Directory Site Contact List Response

See: directorySiteContactsListResponse smart constructor.

Instances

Eq DirectorySiteContactsListResponse Source # 
Data DirectorySiteContactsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectorySiteContactsListResponse -> c DirectorySiteContactsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectorySiteContactsListResponse #

toConstr :: DirectorySiteContactsListResponse -> Constr #

dataTypeOf :: DirectorySiteContactsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectorySiteContactsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectorySiteContactsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> DirectorySiteContactsListResponse -> DirectorySiteContactsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteContactsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteContactsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectorySiteContactsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectorySiteContactsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectorySiteContactsListResponse -> m DirectorySiteContactsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteContactsListResponse -> m DirectorySiteContactsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteContactsListResponse -> m DirectorySiteContactsListResponse #

Show DirectorySiteContactsListResponse Source # 
Generic DirectorySiteContactsListResponse Source # 
ToJSON DirectorySiteContactsListResponse Source # 
FromJSON DirectorySiteContactsListResponse Source # 
type Rep DirectorySiteContactsListResponse Source # 
type Rep DirectorySiteContactsListResponse = D1 (MetaData "DirectorySiteContactsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DirectorySiteContactsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dsclrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_dsclrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_dsclrDirectorySiteContacts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DirectorySiteContact]))))))

directorySiteContactsListResponse :: DirectorySiteContactsListResponse Source #

Creates a value of DirectorySiteContactsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dsclrNextPageToken :: Lens' DirectorySiteContactsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

dsclrKind :: Lens' DirectorySiteContactsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#directorySiteContactsListResponse".

Region

data Region Source #

Contains information about a region that can be targeted by ads.

See: region smart constructor.

Instances

Eq Region Source # 

Methods

(==) :: Region -> Region -> Bool #

(/=) :: Region -> Region -> Bool #

Data Region Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Region -> c Region #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Region #

toConstr :: Region -> Constr #

dataTypeOf :: Region -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Region) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region) #

gmapT :: (forall b. Data b => b -> b) -> Region -> Region #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r #

gmapQ :: (forall d. Data d => d -> u) -> Region -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Region -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Region -> m Region #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region #

Show Region Source # 
Generic Region Source # 

Associated Types

type Rep Region :: * -> * #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

ToJSON Region Source # 
FromJSON Region Source # 
type Rep Region Source # 
type Rep Region = D1 (MetaData "Region" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Region'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_regRegionCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_regKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_regName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_regCountryCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_regCountryDartId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_regDartId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))))

region :: Region Source #

Creates a value of Region with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

regKind :: Lens' Region Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#region".

regName :: Lens' Region (Maybe Text) Source #

Name of this region.

regCountryCode :: Lens' Region (Maybe Text) Source #

Country code of the country to which this region belongs.

regCountryDartId :: Lens' Region (Maybe Int64) Source #

DART ID of the country to which this region belongs.

regDartId :: Lens' Region (Maybe Int64) Source #

DART ID of this region.

AdvertiserGroupsListResponse

data AdvertiserGroupsListResponse Source #

Advertiser Group List Response

See: advertiserGroupsListResponse smart constructor.

Instances

Eq AdvertiserGroupsListResponse Source # 
Data AdvertiserGroupsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdvertiserGroupsListResponse -> c AdvertiserGroupsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdvertiserGroupsListResponse #

toConstr :: AdvertiserGroupsListResponse -> Constr #

dataTypeOf :: AdvertiserGroupsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdvertiserGroupsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdvertiserGroupsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> AdvertiserGroupsListResponse -> AdvertiserGroupsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdvertiserGroupsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdvertiserGroupsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdvertiserGroupsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdvertiserGroupsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdvertiserGroupsListResponse -> m AdvertiserGroupsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertiserGroupsListResponse -> m AdvertiserGroupsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertiserGroupsListResponse -> m AdvertiserGroupsListResponse #

Show AdvertiserGroupsListResponse Source # 
Generic AdvertiserGroupsListResponse Source # 
ToJSON AdvertiserGroupsListResponse Source # 
FromJSON AdvertiserGroupsListResponse Source # 
type Rep AdvertiserGroupsListResponse Source # 
type Rep AdvertiserGroupsListResponse = D1 (MetaData "AdvertiserGroupsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "AdvertiserGroupsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_aglrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_aglrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_aglrAdvertiserGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [AdvertiserGroup]))))))

advertiserGroupsListResponse :: AdvertiserGroupsListResponse Source #

Creates a value of AdvertiserGroupsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

aglrNextPageToken :: Lens' AdvertiserGroupsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

aglrKind :: Lens' AdvertiserGroupsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#advertiserGroupsListResponse".

AdsListSortOrder

data AdsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

ADSAscending
ASCENDING
ADSDescending
DESCENDING

Instances

Enum AdsListSortOrder Source # 
Eq AdsListSortOrder Source # 
Data AdsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdsListSortOrder -> c AdsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdsListSortOrder #

toConstr :: AdsListSortOrder -> Constr #

dataTypeOf :: AdsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> AdsListSortOrder -> AdsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdsListSortOrder -> m AdsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdsListSortOrder -> m AdsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdsListSortOrder -> m AdsListSortOrder #

Ord AdsListSortOrder Source # 
Read AdsListSortOrder Source # 
Show AdsListSortOrder Source # 
Generic AdsListSortOrder Source # 
Hashable AdsListSortOrder Source # 
ToJSON AdsListSortOrder Source # 
FromJSON AdsListSortOrder Source # 
FromHttpApiData AdsListSortOrder Source # 
ToHttpApiData AdsListSortOrder Source # 
type Rep AdsListSortOrder Source # 
type Rep AdsListSortOrder = D1 (MetaData "AdsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ADSAscending" PrefixI False) U1) (C1 (MetaCons "ADSDescending" PrefixI False) U1))

ProjectsListSortOrder

data ProjectsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

PLSOAscending
ASCENDING
PLSODescending
DESCENDING

Instances

Enum ProjectsListSortOrder Source # 
Eq ProjectsListSortOrder Source # 
Data ProjectsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProjectsListSortOrder -> c ProjectsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProjectsListSortOrder #

toConstr :: ProjectsListSortOrder -> Constr #

dataTypeOf :: ProjectsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProjectsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProjectsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> ProjectsListSortOrder -> ProjectsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProjectsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProjectsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProjectsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProjectsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProjectsListSortOrder -> m ProjectsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProjectsListSortOrder -> m ProjectsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProjectsListSortOrder -> m ProjectsListSortOrder #

Ord ProjectsListSortOrder Source # 
Read ProjectsListSortOrder Source # 
Show ProjectsListSortOrder Source # 
Generic ProjectsListSortOrder Source # 
Hashable ProjectsListSortOrder Source # 
ToJSON ProjectsListSortOrder Source # 
FromJSON ProjectsListSortOrder Source # 
FromHttpApiData ProjectsListSortOrder Source # 
ToHttpApiData ProjectsListSortOrder Source # 
type Rep ProjectsListSortOrder Source # 
type Rep ProjectsListSortOrder = D1 (MetaData "ProjectsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PLSOAscending" PrefixI False) U1) (C1 (MetaCons "PLSODescending" PrefixI False) U1))

CreativeAssignment

data CreativeAssignment Source #

Creative Assignment.

See: creativeAssignment smart constructor.

Instances

Eq CreativeAssignment Source # 
Data CreativeAssignment Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssignment -> c CreativeAssignment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssignment #

toConstr :: CreativeAssignment -> Constr #

dataTypeOf :: CreativeAssignment -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssignment) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssignment) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssignment -> CreativeAssignment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssignment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssignment -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssignment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssignment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssignment -> m CreativeAssignment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssignment -> m CreativeAssignment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssignment -> m CreativeAssignment #

Show CreativeAssignment Source # 
Generic CreativeAssignment Source # 
ToJSON CreativeAssignment Source # 
FromJSON CreativeAssignment Source # 
type Rep CreativeAssignment Source # 
type Rep CreativeAssignment = D1 (MetaData "CreativeAssignment" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeAssignment'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_caCreativeGroupAssignments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeGroupAssignment]))) ((:*:) (S1 (MetaSel (Just Symbol "_caStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_caWeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))) ((:*:) (S1 (MetaSel (Just Symbol "_caRichMediaExitOverrides") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RichMediaExitOverride]))) ((:*:) (S1 (MetaSel (Just Symbol "_caSSLCompliant") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_caCreativeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_caClickThroughURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ClickThroughURL))) ((:*:) (S1 (MetaSel (Just Symbol "_caApplyEventTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_caActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_caSequence") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_caEndTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')))) ((:*:) (S1 (MetaSel (Just Symbol "_caCompanionCreativeOverrides") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CompanionClickThroughOverride]))) (S1 (MetaSel (Just Symbol "_caCreativeIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))))))))

caCreativeGroupAssignments :: Lens' CreativeAssignment [CreativeGroupAssignment] Source #

Creative group assignments for this creative assignment. Only one assignment per creative group number is allowed for a maximum of two assignments.

caStartTime :: Lens' CreativeAssignment (Maybe UTCTime) Source #

Date and time that the assigned creative should start serving.

caWeight :: Lens' CreativeAssignment (Maybe Int32) Source #

Weight of the creative assignment, applicable when the rotation type is CREATIVE_ROTATION_TYPE_RANDOM.

caRichMediaExitOverrides :: Lens' CreativeAssignment [RichMediaExitOverride] Source #

Rich media exit overrides for this creative assignment. Applicable when the creative type is any of the following: - RICH_MEDIA_INPAGE - RICH_MEDIA_INPAGE_FLOATING - RICH_MEDIA_IM_EXPAND - RICH_MEDIA_EXPANDING - RICH_MEDIA_INTERSTITIAL_FLOAT - RICH_MEDIA_MOBILE_IN_APP - RICH_MEDIA_MULTI_FLOATING - RICH_MEDIA_PEEL_DOWN - ADVANCED_BANNER - VPAID_LINEAR - VPAID_NON_LINEAR

caSSLCompliant :: Lens' CreativeAssignment (Maybe Bool) Source #

Whether the creative to be assigned is SSL-compliant. This is a read-only field that is auto-generated when the ad is inserted or updated.

caCreativeId :: Lens' CreativeAssignment (Maybe Int64) Source #

ID of the creative to be assigned. This is a required field.

caClickThroughURL :: Lens' CreativeAssignment (Maybe ClickThroughURL) Source #

Click-through URL of the creative assignment.

caApplyEventTags :: Lens' CreativeAssignment (Maybe Bool) Source #

Whether applicable event tags should fire when this creative assignment is rendered. If this value is unset when the ad is inserted or updated, it will default to true for all creative types EXCEPT for INTERNAL_REDIRECT, INTERSTITIAL_INTERNAL_REDIRECT, and INSTREAM_VIDEO.

caActive :: Lens' CreativeAssignment (Maybe Bool) Source #

Whether this creative assignment is active. When true, the creative will be included in the ad's rotation.

caSequence :: Lens' CreativeAssignment (Maybe Int32) Source #

Sequence number of the creative assignment, applicable when the rotation type is CREATIVE_ROTATION_TYPE_SEQUENTIAL.

caEndTime :: Lens' CreativeAssignment (Maybe UTCTime) Source #

Date and time that the assigned creative should stop serving. Must be later than the start time.

caCompanionCreativeOverrides :: Lens' CreativeAssignment [CompanionClickThroughOverride] Source #

Companion creative overrides for this creative assignment. Applicable to video ads.

caCreativeIdDimensionValue :: Lens' CreativeAssignment (Maybe DimensionValue) Source #

Dimension value for the ID of the creative. This is a read-only, auto-generated field.

DimensionFilter

data DimensionFilter Source #

Represents a dimension filter.

See: dimensionFilter smart constructor.

Instances

Eq DimensionFilter Source # 
Data DimensionFilter Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DimensionFilter -> c DimensionFilter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DimensionFilter #

toConstr :: DimensionFilter -> Constr #

dataTypeOf :: DimensionFilter -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DimensionFilter) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DimensionFilter) #

gmapT :: (forall b. Data b => b -> b) -> DimensionFilter -> DimensionFilter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DimensionFilter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DimensionFilter -> r #

gmapQ :: (forall d. Data d => d -> u) -> DimensionFilter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DimensionFilter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DimensionFilter -> m DimensionFilter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionFilter -> m DimensionFilter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionFilter -> m DimensionFilter #

Show DimensionFilter Source # 
Generic DimensionFilter Source # 
ToJSON DimensionFilter Source # 
FromJSON DimensionFilter Source # 
type Rep DimensionFilter Source # 
type Rep DimensionFilter = D1 (MetaData "DimensionFilter" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DimensionFilter'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dfKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_dfValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dfDimensionName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

dimensionFilter :: DimensionFilter Source #

Creates a value of DimensionFilter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dfKind :: Lens' DimensionFilter Text Source #

The kind of resource this is, in this case dfareporting#dimensionFilter.

dfValue :: Lens' DimensionFilter (Maybe Text) Source #

The value of the dimension to filter.

dfDimensionName :: Lens' DimensionFilter (Maybe Text) Source #

The name of the dimension to filter.

UserProFileList

data UserProFileList Source #

Represents the list of user profiles.

See: userProFileList smart constructor.

Instances

Eq UserProFileList Source # 
Data UserProFileList Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserProFileList -> c UserProFileList #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserProFileList #

toConstr :: UserProFileList -> Constr #

dataTypeOf :: UserProFileList -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserProFileList) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserProFileList) #

gmapT :: (forall b. Data b => b -> b) -> UserProFileList -> UserProFileList #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserProFileList -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserProFileList -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserProFileList -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserProFileList -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserProFileList -> m UserProFileList #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserProFileList -> m UserProFileList #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserProFileList -> m UserProFileList #

Show UserProFileList Source # 
Generic UserProFileList Source # 
ToJSON UserProFileList Source # 
FromJSON UserProFileList Source # 
type Rep UserProFileList Source # 
type Rep UserProFileList = D1 (MetaData "UserProFileList" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "UserProFileList'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_upflEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_upflKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_upflItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UserProFile]))))))

userProFileList :: UserProFileList Source #

Creates a value of UserProFileList with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

upflEtag :: Lens' UserProFileList (Maybe Text) Source #

The eTag of this response for caching purposes.

upflKind :: Lens' UserProFileList Text Source #

The kind of list this is, in this case dfareporting#userProfileList.

upflItems :: Lens' UserProFileList [UserProFile] Source #

The user profiles returned in this response.

RemarketingListsListSortField

data RemarketingListsListSortField Source #

Field by which to sort the list.

Constructors

RLLSFID
ID
RLLSFName
NAME

Instances

Enum RemarketingListsListSortField Source # 
Eq RemarketingListsListSortField Source # 
Data RemarketingListsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RemarketingListsListSortField -> c RemarketingListsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RemarketingListsListSortField #

toConstr :: RemarketingListsListSortField -> Constr #

dataTypeOf :: RemarketingListsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RemarketingListsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RemarketingListsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> RemarketingListsListSortField -> RemarketingListsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RemarketingListsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RemarketingListsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> RemarketingListsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RemarketingListsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RemarketingListsListSortField -> m RemarketingListsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RemarketingListsListSortField -> m RemarketingListsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RemarketingListsListSortField -> m RemarketingListsListSortField #

Ord RemarketingListsListSortField Source # 
Read RemarketingListsListSortField Source # 
Show RemarketingListsListSortField Source # 
Generic RemarketingListsListSortField Source # 
Hashable RemarketingListsListSortField Source # 
ToJSON RemarketingListsListSortField Source # 
FromJSON RemarketingListsListSortField Source # 
FromHttpApiData RemarketingListsListSortField Source # 
ToHttpApiData RemarketingListsListSortField Source # 
type Rep RemarketingListsListSortField Source # 
type Rep RemarketingListsListSortField = D1 (MetaData "RemarketingListsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "RLLSFID" PrefixI False) U1) (C1 (MetaCons "RLLSFName" PrefixI False) U1))

FloodlightConfiguration

data FloodlightConfiguration Source #

Contains properties of a Floodlight configuration.

See: floodlightConfiguration smart constructor.

Instances

Eq FloodlightConfiguration Source # 
Data FloodlightConfiguration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightConfiguration -> c FloodlightConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightConfiguration #

toConstr :: FloodlightConfiguration -> Constr #

dataTypeOf :: FloodlightConfiguration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightConfiguration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightConfiguration -> FloodlightConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightConfiguration -> m FloodlightConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightConfiguration -> m FloodlightConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightConfiguration -> m FloodlightConfiguration #

Show FloodlightConfiguration Source # 
Generic FloodlightConfiguration Source # 
ToJSON FloodlightConfiguration Source # 
FromJSON FloodlightConfiguration Source # 
type Rep FloodlightConfiguration Source # 
type Rep FloodlightConfiguration = D1 (MetaData "FloodlightConfiguration" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FloodlightConfiguration'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_fcTagSettings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TagSettings))) (S1 (MetaSel (Just Symbol "_fcExposureToConversionEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_fcInAppAttributionTrackingEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_fcThirdPartyAuthenticationTokens") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ThirdPartyAuthenticationToken]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_fcKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_fcAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_fcAnalyticsDataSharingEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_fcAdvertiserIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_fcIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_fcLookbackConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LookbackConfiguration))) (S1 (MetaSel (Just Symbol "_fcAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_fcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_fcNATuralSearchConversionAttributionOption") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FloodlightConfigurationNATuralSearchConversionAttributionOption))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_fcUserDefinedVariableConfigurations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UserDefinedVariableConfiguration]))) (S1 (MetaSel (Just Symbol "_fcSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_fcFirstDayOfWeek") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FloodlightConfigurationFirstDayOfWeek))) ((:*:) (S1 (MetaSel (Just Symbol "_fcOmnitureSettings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe OmnitureSettings))) (S1 (MetaSel (Just Symbol "_fcStandardVariableTypes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [FloodlightConfigurationStandardVariableTypesItem])))))))))

fcTagSettings :: Lens' FloodlightConfiguration (Maybe TagSettings) Source #

Configuration settings for dynamic and image floodlight tags.

fcExposureToConversionEnabled :: Lens' FloodlightConfiguration (Maybe Bool) Source #

Whether the exposure-to-conversion report is enabled. This report shows detailed pathway information on up to 10 of the most recent ad exposures seen by a user before converting.

fcInAppAttributionTrackingEnabled :: Lens' FloodlightConfiguration (Maybe Bool) Source #

Whether in-app attribution tracking is enabled.

fcThirdPartyAuthenticationTokens :: Lens' FloodlightConfiguration [ThirdPartyAuthenticationToken] Source #

List of third-party authentication tokens enabled for this configuration.

fcKind :: Lens' FloodlightConfiguration Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#floodlightConfiguration".

fcAdvertiserId :: Lens' FloodlightConfiguration (Maybe Int64) Source #

Advertiser ID of the parent advertiser of this floodlight configuration.

fcAnalyticsDataSharingEnabled :: Lens' FloodlightConfiguration (Maybe Bool) Source #

Whether advertiser data is shared with Google Analytics.

fcAdvertiserIdDimensionValue :: Lens' FloodlightConfiguration (Maybe DimensionValue) Source #

Dimension value for the ID of the advertiser. This is a read-only, auto-generated field.

fcIdDimensionValue :: Lens' FloodlightConfiguration (Maybe DimensionValue) Source #

Dimension value for the ID of this floodlight configuration. This is a read-only, auto-generated field.

fcLookbackConfiguration :: Lens' FloodlightConfiguration (Maybe LookbackConfiguration) Source #

Lookback window settings for this floodlight configuration.

fcAccountId :: Lens' FloodlightConfiguration (Maybe Int64) Source #

Account ID of this floodlight configuration. This is a read-only field that can be left blank.

fcId :: Lens' FloodlightConfiguration (Maybe Int64) Source #

ID of this floodlight configuration. This is a read-only, auto-generated field.

fcUserDefinedVariableConfigurations :: Lens' FloodlightConfiguration [UserDefinedVariableConfiguration] Source #

List of user defined variables enabled for this configuration.

fcSubAccountId :: Lens' FloodlightConfiguration (Maybe Int64) Source #

Subaccount ID of this floodlight configuration. This is a read-only field that can be left blank.

fcFirstDayOfWeek :: Lens' FloodlightConfiguration (Maybe FloodlightConfigurationFirstDayOfWeek) Source #

Day that will be counted as the first day of the week in reports. This is a required field.

fcStandardVariableTypes :: Lens' FloodlightConfiguration [FloodlightConfigurationStandardVariableTypesItem] Source #

List of standard variables enabled for this configuration. Acceptable values are: - "ORD" - "NUM"

ReportScheduleRepeatsOnWeekDaysItem

data ReportScheduleRepeatsOnWeekDaysItem Source #

Instances

Enum ReportScheduleRepeatsOnWeekDaysItem Source # 
Eq ReportScheduleRepeatsOnWeekDaysItem Source # 
Data ReportScheduleRepeatsOnWeekDaysItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportScheduleRepeatsOnWeekDaysItem -> c ReportScheduleRepeatsOnWeekDaysItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportScheduleRepeatsOnWeekDaysItem #

toConstr :: ReportScheduleRepeatsOnWeekDaysItem -> Constr #

dataTypeOf :: ReportScheduleRepeatsOnWeekDaysItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportScheduleRepeatsOnWeekDaysItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportScheduleRepeatsOnWeekDaysItem) #

gmapT :: (forall b. Data b => b -> b) -> ReportScheduleRepeatsOnWeekDaysItem -> ReportScheduleRepeatsOnWeekDaysItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportScheduleRepeatsOnWeekDaysItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportScheduleRepeatsOnWeekDaysItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportScheduleRepeatsOnWeekDaysItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportScheduleRepeatsOnWeekDaysItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportScheduleRepeatsOnWeekDaysItem -> m ReportScheduleRepeatsOnWeekDaysItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportScheduleRepeatsOnWeekDaysItem -> m ReportScheduleRepeatsOnWeekDaysItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportScheduleRepeatsOnWeekDaysItem -> m ReportScheduleRepeatsOnWeekDaysItem #

Ord ReportScheduleRepeatsOnWeekDaysItem Source # 
Read ReportScheduleRepeatsOnWeekDaysItem Source # 
Show ReportScheduleRepeatsOnWeekDaysItem Source # 
Generic ReportScheduleRepeatsOnWeekDaysItem Source # 
Hashable ReportScheduleRepeatsOnWeekDaysItem Source # 
ToJSON ReportScheduleRepeatsOnWeekDaysItem Source # 
FromJSON ReportScheduleRepeatsOnWeekDaysItem Source # 
FromHttpApiData ReportScheduleRepeatsOnWeekDaysItem Source # 
ToHttpApiData ReportScheduleRepeatsOnWeekDaysItem Source # 
type Rep ReportScheduleRepeatsOnWeekDaysItem Source # 
type Rep ReportScheduleRepeatsOnWeekDaysItem = D1 (MetaData "ReportScheduleRepeatsOnWeekDaysItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "RSROWDIFriday" PrefixI False) U1) ((:+:) (C1 (MetaCons "RSROWDIMonday" PrefixI False) U1) (C1 (MetaCons "RSROWDISaturday" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "RSROWDISunday" PrefixI False) U1) (C1 (MetaCons "RSROWDIThursday" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RSROWDITuesday" PrefixI False) U1) (C1 (MetaCons "RSROWDIWednesday" PrefixI False) U1))))

FloodlightActivityGroupsListResponse

data FloodlightActivityGroupsListResponse Source #

Floodlight Activity Group List Response

See: floodlightActivityGroupsListResponse smart constructor.

Instances

Eq FloodlightActivityGroupsListResponse Source # 
Data FloodlightActivityGroupsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivityGroupsListResponse -> c FloodlightActivityGroupsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivityGroupsListResponse #

toConstr :: FloodlightActivityGroupsListResponse -> Constr #

dataTypeOf :: FloodlightActivityGroupsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivityGroupsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivityGroupsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivityGroupsListResponse -> FloodlightActivityGroupsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityGroupsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityGroupsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivityGroupsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivityGroupsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupsListResponse -> m FloodlightActivityGroupsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupsListResponse -> m FloodlightActivityGroupsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupsListResponse -> m FloodlightActivityGroupsListResponse #

Show FloodlightActivityGroupsListResponse Source # 
Generic FloodlightActivityGroupsListResponse Source # 
ToJSON FloodlightActivityGroupsListResponse Source # 
FromJSON FloodlightActivityGroupsListResponse Source # 
type Rep FloodlightActivityGroupsListResponse Source # 
type Rep FloodlightActivityGroupsListResponse = D1 (MetaData "FloodlightActivityGroupsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FloodlightActivityGroupsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_faglrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_faglrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_faglrFloodlightActivityGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [FloodlightActivityGroup]))))))

floodlightActivityGroupsListResponse :: FloodlightActivityGroupsListResponse Source #

Creates a value of FloodlightActivityGroupsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

faglrNextPageToken :: Lens' FloodlightActivityGroupsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

faglrKind :: Lens' FloodlightActivityGroupsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#floodlightActivityGroupsListResponse".

CreativeGroupAssignmentCreativeGroupNumber

data CreativeGroupAssignmentCreativeGroupNumber Source #

Creative group number of the creative group assignment.

Constructors

CreativeGroupOne
CREATIVE_GROUP_ONE
CreativeGroupTwo
CREATIVE_GROUP_TWO

Instances

Enum CreativeGroupAssignmentCreativeGroupNumber Source # 
Eq CreativeGroupAssignmentCreativeGroupNumber Source # 
Data CreativeGroupAssignmentCreativeGroupNumber Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeGroupAssignmentCreativeGroupNumber -> c CreativeGroupAssignmentCreativeGroupNumber #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeGroupAssignmentCreativeGroupNumber #

toConstr :: CreativeGroupAssignmentCreativeGroupNumber -> Constr #

dataTypeOf :: CreativeGroupAssignmentCreativeGroupNumber -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeGroupAssignmentCreativeGroupNumber) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeGroupAssignmentCreativeGroupNumber) #

gmapT :: (forall b. Data b => b -> b) -> CreativeGroupAssignmentCreativeGroupNumber -> CreativeGroupAssignmentCreativeGroupNumber #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeGroupAssignmentCreativeGroupNumber -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeGroupAssignmentCreativeGroupNumber -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeGroupAssignmentCreativeGroupNumber -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeGroupAssignmentCreativeGroupNumber -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeGroupAssignmentCreativeGroupNumber -> m CreativeGroupAssignmentCreativeGroupNumber #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeGroupAssignmentCreativeGroupNumber -> m CreativeGroupAssignmentCreativeGroupNumber #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeGroupAssignmentCreativeGroupNumber -> m CreativeGroupAssignmentCreativeGroupNumber #

Ord CreativeGroupAssignmentCreativeGroupNumber Source # 
Read CreativeGroupAssignmentCreativeGroupNumber Source # 
Show CreativeGroupAssignmentCreativeGroupNumber Source # 
Generic CreativeGroupAssignmentCreativeGroupNumber Source # 
Hashable CreativeGroupAssignmentCreativeGroupNumber Source # 
ToJSON CreativeGroupAssignmentCreativeGroupNumber Source # 
FromJSON CreativeGroupAssignmentCreativeGroupNumber Source # 
FromHttpApiData CreativeGroupAssignmentCreativeGroupNumber Source # 
ToHttpApiData CreativeGroupAssignmentCreativeGroupNumber Source # 
type Rep CreativeGroupAssignmentCreativeGroupNumber Source # 
type Rep CreativeGroupAssignmentCreativeGroupNumber = D1 (MetaData "CreativeGroupAssignmentCreativeGroupNumber" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CreativeGroupOne" PrefixI False) U1) (C1 (MetaCons "CreativeGroupTwo" PrefixI False) U1))

Conversion

data Conversion Source #

A Conversion represents when a user successfully performs a desired action after seeing an ad.

See: conversion smart constructor.

Instances

Eq Conversion Source # 
Data Conversion Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Conversion -> c Conversion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Conversion #

toConstr :: Conversion -> Constr #

dataTypeOf :: Conversion -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Conversion) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Conversion) #

gmapT :: (forall b. Data b => b -> b) -> Conversion -> Conversion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Conversion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Conversion -> r #

gmapQ :: (forall d. Data d => d -> u) -> Conversion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Conversion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Conversion -> m Conversion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Conversion -> m Conversion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Conversion -> m Conversion #

Show Conversion Source # 
Generic Conversion Source # 

Associated Types

type Rep Conversion :: * -> * #

ToJSON Conversion Source # 
FromJSON Conversion Source # 
type Rep Conversion Source # 
type Rep Conversion = D1 (MetaData "Conversion" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Conversion'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_conoTimestampMicros") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_conoLimitAdTracking") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_conoEncryptedUserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_conoMobileDeviceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_conoFloodlightConfigurationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_conoKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_conoFloodlightActivityId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_conoQuantity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_conoValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))))) ((:*:) (S1 (MetaSel (Just Symbol "_conoCustomVariables") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CustomFloodlightVariable]))) ((:*:) (S1 (MetaSel (Just Symbol "_conoChildDirectedTreatment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_conoOrdinal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

conoTimestampMicros :: Lens' Conversion (Maybe Int64) Source #

The timestamp of conversion, in Unix epoch micros. This is a required field.

conoLimitAdTracking :: Lens' Conversion (Maybe Bool) Source #

Whether the user has Limit Ad Tracking set.

conoEncryptedUserId :: Lens' Conversion (Maybe Text) Source #

The alphanumeric encrypted user ID. When set, encryptionInfo should also be specified. This field is mutually exclusive with mobileDeviceId. This or mobileDeviceId is a required field.

conoMobileDeviceId :: Lens' Conversion (Maybe Text) Source #

The mobile device ID. This field is mutually exclusive with encryptedUserId. This or encryptedUserId is a required field.

conoFloodlightConfigurationId :: Lens' Conversion (Maybe Int64) Source #

Floodlight Configuration ID of this conversion. This is a required field.

conoKind :: Lens' Conversion Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#conversion".

conoFloodlightActivityId :: Lens' Conversion (Maybe Int64) Source #

Floodlight Activity ID of this conversion. This is a required field.

conoQuantity :: Lens' Conversion (Maybe Int64) Source #

The quantity of the conversion.

conoValue :: Lens' Conversion (Maybe Double) Source #

The value of the conversion.

conoChildDirectedTreatment :: Lens' Conversion (Maybe Bool) Source #

Whether the conversion was directed toward children.

conoOrdinal :: Lens' Conversion (Maybe Text) Source #

The ordinal of the conversion. Use this field to control how conversions of the same user and day are de-duplicated. This is a required field.

CreativeFieldValuesListResponse

data CreativeFieldValuesListResponse Source #

Creative Field Value List Response

See: creativeFieldValuesListResponse smart constructor.

Instances

Eq CreativeFieldValuesListResponse Source # 
Data CreativeFieldValuesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeFieldValuesListResponse -> c CreativeFieldValuesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeFieldValuesListResponse #

toConstr :: CreativeFieldValuesListResponse -> Constr #

dataTypeOf :: CreativeFieldValuesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeFieldValuesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeFieldValuesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> CreativeFieldValuesListResponse -> CreativeFieldValuesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeFieldValuesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeFieldValuesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeFieldValuesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeFieldValuesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeFieldValuesListResponse -> m CreativeFieldValuesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeFieldValuesListResponse -> m CreativeFieldValuesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeFieldValuesListResponse -> m CreativeFieldValuesListResponse #

Show CreativeFieldValuesListResponse Source # 
Generic CreativeFieldValuesListResponse Source # 
ToJSON CreativeFieldValuesListResponse Source # 
FromJSON CreativeFieldValuesListResponse Source # 
type Rep CreativeFieldValuesListResponse Source # 
type Rep CreativeFieldValuesListResponse = D1 (MetaData "CreativeFieldValuesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeFieldValuesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cfvlrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cfvlrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_cfvlrCreativeFieldValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeFieldValue]))))))

creativeFieldValuesListResponse :: CreativeFieldValuesListResponse Source #

Creates a value of CreativeFieldValuesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cfvlrNextPageToken :: Lens' CreativeFieldValuesListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

cfvlrKind :: Lens' CreativeFieldValuesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#creativeFieldValuesListResponse".

AccountsListSortField

data AccountsListSortField Source #

Field by which to sort the list.

Constructors

AID
ID
AName
NAME

Instances

Enum AccountsListSortField Source # 
Eq AccountsListSortField Source # 
Data AccountsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountsListSortField -> c AccountsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountsListSortField #

toConstr :: AccountsListSortField -> Constr #

dataTypeOf :: AccountsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> AccountsListSortField -> AccountsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountsListSortField -> m AccountsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountsListSortField -> m AccountsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountsListSortField -> m AccountsListSortField #

Ord AccountsListSortField Source # 
Read AccountsListSortField Source # 
Show AccountsListSortField Source # 
Generic AccountsListSortField Source # 
Hashable AccountsListSortField Source # 
ToJSON AccountsListSortField Source # 
FromJSON AccountsListSortField Source # 
FromHttpApiData AccountsListSortField Source # 
ToHttpApiData AccountsListSortField Source # 
type Rep AccountsListSortField Source # 
type Rep AccountsListSortField = D1 (MetaData "AccountsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "AID" PrefixI False) U1) (C1 (MetaCons "AName" PrefixI False) U1))

RichMediaExitOverride

data RichMediaExitOverride Source #

Rich Media Exit Override.

See: richMediaExitOverride smart constructor.

Instances

Eq RichMediaExitOverride Source # 
Data RichMediaExitOverride Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RichMediaExitOverride -> c RichMediaExitOverride #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RichMediaExitOverride #

toConstr :: RichMediaExitOverride -> Constr #

dataTypeOf :: RichMediaExitOverride -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RichMediaExitOverride) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RichMediaExitOverride) #

gmapT :: (forall b. Data b => b -> b) -> RichMediaExitOverride -> RichMediaExitOverride #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RichMediaExitOverride -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RichMediaExitOverride -> r #

gmapQ :: (forall d. Data d => d -> u) -> RichMediaExitOverride -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RichMediaExitOverride -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RichMediaExitOverride -> m RichMediaExitOverride #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RichMediaExitOverride -> m RichMediaExitOverride #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RichMediaExitOverride -> m RichMediaExitOverride #

Show RichMediaExitOverride Source # 
Generic RichMediaExitOverride Source # 
ToJSON RichMediaExitOverride Source # 
FromJSON RichMediaExitOverride Source # 
type Rep RichMediaExitOverride Source # 
type Rep RichMediaExitOverride = D1 (MetaData "RichMediaExitOverride" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "RichMediaExitOverride'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rmeoUseCustomExitURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_rmeoExitId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_rmeoCustomExitURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

richMediaExitOverride :: RichMediaExitOverride Source #

Creates a value of RichMediaExitOverride with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rmeoUseCustomExitURL :: Lens' RichMediaExitOverride (Maybe Bool) Source #

Whether to use the custom exit URL.

rmeoExitId :: Lens' RichMediaExitOverride (Maybe Int64) Source #

ID for the override to refer to a specific exit in the creative.

rmeoCustomExitURL :: Lens' RichMediaExitOverride (Maybe Text) Source #

Click-through URL to override the default exit URL. Applicable if the useCustomExitUrl field is set to true.

AdvertisersListStatus

data AdvertisersListStatus Source #

Select only advertisers with the specified status.

Constructors

Approved
APPROVED
OnHold
ON_HOLD

Instances

Enum AdvertisersListStatus Source # 
Eq AdvertisersListStatus Source # 
Data AdvertisersListStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdvertisersListStatus -> c AdvertisersListStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdvertisersListStatus #

toConstr :: AdvertisersListStatus -> Constr #

dataTypeOf :: AdvertisersListStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdvertisersListStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdvertisersListStatus) #

gmapT :: (forall b. Data b => b -> b) -> AdvertisersListStatus -> AdvertisersListStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdvertisersListStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdvertisersListStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdvertisersListStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdvertisersListStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdvertisersListStatus -> m AdvertisersListStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertisersListStatus -> m AdvertisersListStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertisersListStatus -> m AdvertisersListStatus #

Ord AdvertisersListStatus Source # 
Read AdvertisersListStatus Source # 
Show AdvertisersListStatus Source # 
Generic AdvertisersListStatus Source # 
Hashable AdvertisersListStatus Source # 
ToJSON AdvertisersListStatus Source # 
FromJSON AdvertisersListStatus Source # 
FromHttpApiData AdvertisersListStatus Source # 
ToHttpApiData AdvertisersListStatus Source # 
type Rep AdvertisersListStatus Source # 
type Rep AdvertisersListStatus = D1 (MetaData "AdvertisersListStatus" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "Approved" PrefixI False) U1) (C1 (MetaCons "OnHold" PrefixI False) U1))

DimensionValueMatchType

data DimensionValueMatchType Source #

Determines how the 'value' field is matched when filtering. If not specified, defaults to EXACT. If set to WILDCARD_EXPRESSION, '*' is allowed as a placeholder for variable length character sequences, and it can be escaped with a backslash. Note, only paid search dimensions ('dfa:paidSearch*') allow a matchType other than EXACT.

Constructors

BeginsWith
BEGINS_WITH
Contains
CONTAINS
Exact
EXACT
WildcardExpression
WILDCARD_EXPRESSION

Instances

Enum DimensionValueMatchType Source # 
Eq DimensionValueMatchType Source # 
Data DimensionValueMatchType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DimensionValueMatchType -> c DimensionValueMatchType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DimensionValueMatchType #

toConstr :: DimensionValueMatchType -> Constr #

dataTypeOf :: DimensionValueMatchType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DimensionValueMatchType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DimensionValueMatchType) #

gmapT :: (forall b. Data b => b -> b) -> DimensionValueMatchType -> DimensionValueMatchType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DimensionValueMatchType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DimensionValueMatchType -> r #

gmapQ :: (forall d. Data d => d -> u) -> DimensionValueMatchType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DimensionValueMatchType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DimensionValueMatchType -> m DimensionValueMatchType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionValueMatchType -> m DimensionValueMatchType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionValueMatchType -> m DimensionValueMatchType #

Ord DimensionValueMatchType Source # 
Read DimensionValueMatchType Source # 
Show DimensionValueMatchType Source # 
Generic DimensionValueMatchType Source # 
Hashable DimensionValueMatchType Source # 
ToJSON DimensionValueMatchType Source # 
FromJSON DimensionValueMatchType Source # 
FromHttpApiData DimensionValueMatchType Source # 
ToHttpApiData DimensionValueMatchType Source # 
type Rep DimensionValueMatchType Source # 
type Rep DimensionValueMatchType = D1 (MetaData "DimensionValueMatchType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "BeginsWith" PrefixI False) U1) (C1 (MetaCons "Contains" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Exact" PrefixI False) U1) (C1 (MetaCons "WildcardExpression" PrefixI False) U1)))

SortedDimension

data SortedDimension Source #

Represents a sorted dimension.

See: sortedDimension smart constructor.

Instances

Eq SortedDimension Source # 
Data SortedDimension Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SortedDimension -> c SortedDimension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SortedDimension #

toConstr :: SortedDimension -> Constr #

dataTypeOf :: SortedDimension -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SortedDimension) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortedDimension) #

gmapT :: (forall b. Data b => b -> b) -> SortedDimension -> SortedDimension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortedDimension -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortedDimension -> r #

gmapQ :: (forall d. Data d => d -> u) -> SortedDimension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SortedDimension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SortedDimension -> m SortedDimension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SortedDimension -> m SortedDimension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SortedDimension -> m SortedDimension #

Show SortedDimension Source # 
Generic SortedDimension Source # 
ToJSON SortedDimension Source # 
FromJSON SortedDimension Source # 
type Rep SortedDimension Source # 
type Rep SortedDimension = D1 (MetaData "SortedDimension" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "SortedDimension'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sdKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_sdSortOrder") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SortedDimensionSortOrder))) (S1 (MetaSel (Just Symbol "_sdName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

sortedDimension :: SortedDimension Source #

Creates a value of SortedDimension with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sdKind :: Lens' SortedDimension Text Source #

The kind of resource this is, in this case dfareporting#sortedDimension.

sdSortOrder :: Lens' SortedDimension (Maybe SortedDimensionSortOrder) Source #

An optional sort order for the dimension column.

sdName :: Lens' SortedDimension (Maybe Text) Source #

The name of the dimension.

PlacementGroupsListSortOrder

data PlacementGroupsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

PGLSOAscending
ASCENDING
PGLSODescending
DESCENDING

Instances

Enum PlacementGroupsListSortOrder Source # 
Eq PlacementGroupsListSortOrder Source # 
Data PlacementGroupsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementGroupsListSortOrder -> c PlacementGroupsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementGroupsListSortOrder #

toConstr :: PlacementGroupsListSortOrder -> Constr #

dataTypeOf :: PlacementGroupsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementGroupsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementGroupsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> PlacementGroupsListSortOrder -> PlacementGroupsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroupsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroupsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementGroupsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementGroupsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementGroupsListSortOrder -> m PlacementGroupsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroupsListSortOrder -> m PlacementGroupsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroupsListSortOrder -> m PlacementGroupsListSortOrder #

Ord PlacementGroupsListSortOrder Source # 
Read PlacementGroupsListSortOrder Source # 
Show PlacementGroupsListSortOrder Source # 
Generic PlacementGroupsListSortOrder Source # 
Hashable PlacementGroupsListSortOrder Source # 
ToJSON PlacementGroupsListSortOrder Source # 
FromJSON PlacementGroupsListSortOrder Source # 
FromHttpApiData PlacementGroupsListSortOrder Source # 
ToHttpApiData PlacementGroupsListSortOrder Source # 
type Rep PlacementGroupsListSortOrder Source # 
type Rep PlacementGroupsListSortOrder = D1 (MetaData "PlacementGroupsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PGLSOAscending" PrefixI False) U1) (C1 (MetaCons "PGLSODescending" PrefixI False) U1))

CreativeFieldsListResponse

data CreativeFieldsListResponse Source #

Creative Field List Response

See: creativeFieldsListResponse smart constructor.

Instances

Eq CreativeFieldsListResponse Source # 
Data CreativeFieldsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeFieldsListResponse -> c CreativeFieldsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeFieldsListResponse #

toConstr :: CreativeFieldsListResponse -> Constr #

dataTypeOf :: CreativeFieldsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeFieldsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeFieldsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> CreativeFieldsListResponse -> CreativeFieldsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeFieldsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeFieldsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeFieldsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeFieldsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeFieldsListResponse -> m CreativeFieldsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeFieldsListResponse -> m CreativeFieldsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeFieldsListResponse -> m CreativeFieldsListResponse #

Show CreativeFieldsListResponse Source # 
Generic CreativeFieldsListResponse Source # 
ToJSON CreativeFieldsListResponse Source # 
FromJSON CreativeFieldsListResponse Source # 
type Rep CreativeFieldsListResponse Source # 
type Rep CreativeFieldsListResponse = D1 (MetaData "CreativeFieldsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeFieldsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cflrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cflrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_cflrCreativeFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeField]))))))

creativeFieldsListResponse :: CreativeFieldsListResponse Source #

Creates a value of CreativeFieldsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cflrNextPageToken :: Lens' CreativeFieldsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

cflrKind :: Lens' CreativeFieldsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#creativeFieldsListResponse".

PlacementsGenerateTagsResponse

data PlacementsGenerateTagsResponse Source #

Placement GenerateTags Response

See: placementsGenerateTagsResponse smart constructor.

Instances

Eq PlacementsGenerateTagsResponse Source # 
Data PlacementsGenerateTagsResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementsGenerateTagsResponse -> c PlacementsGenerateTagsResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementsGenerateTagsResponse #

toConstr :: PlacementsGenerateTagsResponse -> Constr #

dataTypeOf :: PlacementsGenerateTagsResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementsGenerateTagsResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementsGenerateTagsResponse) #

gmapT :: (forall b. Data b => b -> b) -> PlacementsGenerateTagsResponse -> PlacementsGenerateTagsResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementsGenerateTagsResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementsGenerateTagsResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementsGenerateTagsResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementsGenerateTagsResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementsGenerateTagsResponse -> m PlacementsGenerateTagsResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementsGenerateTagsResponse -> m PlacementsGenerateTagsResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementsGenerateTagsResponse -> m PlacementsGenerateTagsResponse #

Show PlacementsGenerateTagsResponse Source # 
Generic PlacementsGenerateTagsResponse Source # 
ToJSON PlacementsGenerateTagsResponse Source # 
FromJSON PlacementsGenerateTagsResponse Source # 
type Rep PlacementsGenerateTagsResponse Source # 
type Rep PlacementsGenerateTagsResponse = D1 (MetaData "PlacementsGenerateTagsResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PlacementsGenerateTagsResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pgtrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_pgtrPlacementTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PlacementTag])))))

placementsGenerateTagsResponse :: PlacementsGenerateTagsResponse Source #

Creates a value of PlacementsGenerateTagsResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pgtrKind :: Lens' PlacementsGenerateTagsResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#placementsGenerateTagsResponse".

pgtrPlacementTags :: Lens' PlacementsGenerateTagsResponse [PlacementTag] Source #

Set of generated tags for the specified placements.

CreativeAsset

data CreativeAsset Source #

Creative Asset.

See: creativeAsset smart constructor.

Instances

Eq CreativeAsset Source # 
Data CreativeAsset Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAsset -> c CreativeAsset #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAsset #

toConstr :: CreativeAsset -> Constr #

dataTypeOf :: CreativeAsset -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAsset) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAsset) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAsset -> CreativeAsset #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAsset -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAsset -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAsset -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAsset -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAsset -> m CreativeAsset #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAsset -> m CreativeAsset #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAsset -> m CreativeAsset #

Show CreativeAsset Source # 
Generic CreativeAsset Source # 

Associated Types

type Rep CreativeAsset :: * -> * #

ToJSON CreativeAsset Source # 
FromJSON CreativeAsset Source # 
type Rep CreativeAsset Source # 
type Rep CreativeAsset = D1 (MetaData "CreativeAsset" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeAsset'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_caaZIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_caaPushdown") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_caaVideoDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) ((:*:) (S1 (MetaSel (Just Symbol "_caaOriginalBackup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_caaWindowMode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetWindowMode)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_caaFlashVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_caaPushdownDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))) ((:*:) (S1 (MetaSel (Just Symbol "_caaSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Size))) ((:*:) (S1 (MetaSel (Just Symbol "_caaVerticallyLocked") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_caaOffSet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe OffSetPosition))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_caaStreamingServingURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_caaZipFilesize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_caaTransparency") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_caaHideSelectionBoxes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_caaSSLCompliant") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_caaFileSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_caaAssetIdentifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetId))) (S1 (MetaSel (Just Symbol "_caaDurationType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetDurationType))))) ((:*:) (S1 (MetaSel (Just Symbol "_caaProgressiveServingURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_caaActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_caaRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetRole)))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_caaMimeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_caaPositionTopUnit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetPositionTopUnit)))) ((:*:) (S1 (MetaSel (Just Symbol "_caaPositionLeftUnit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetPositionLeftUnit))) ((:*:) (S1 (MetaSel (Just Symbol "_caaAlignment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetAlignment))) (S1 (MetaSel (Just Symbol "_caaExpandedDimension") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Size)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_caaZipFilename") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_caaActionScript3") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_caaDisplayType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetDisplayType))) ((:*:) (S1 (MetaSel (Just Symbol "_caaChildAssetType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetChildAssetType))) (S1 (MetaSel (Just Symbol "_caaCollapsedSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Size))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_caaId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_caaBitRate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) ((:*:) (S1 (MetaSel (Just Symbol "_caaCustomStartTimeValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_caaStartTimeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetStartTimeType))) (S1 (MetaSel (Just Symbol "_caaDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_caaArtworkType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetArtworkType))) ((:*:) (S1 (MetaSel (Just Symbol "_caaHideFlashObjects") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_caaDetectedFeatures") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeAssetDetectedFeaturesItem]))))) ((:*:) (S1 (MetaSel (Just Symbol "_caaBackupImageExit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeCustomEvent))) ((:*:) (S1 (MetaSel (Just Symbol "_caaPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe OffSetPosition))) (S1 (MetaSel (Just Symbol "_caaHorizontallyLocked") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))))))

caaZIndex :: Lens' CreativeAsset (Maybe Int32) Source #

zIndex value of an asset. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA.Additionally, only applicable to assets whose displayType is NOT one of the following types: ASSET_DISPLAY_TYPE_INPAGE or ASSET_DISPLAY_TYPE_OVERLAY.

caaPushdown :: Lens' CreativeAsset (Maybe Bool) Source #

Whether the asset pushes down other content. Applicable to the following creative types: all RICH_MEDIA. Additionally, only applicable when the asset offsets are 0, the collapsedSize.width matches size.width, and the collapsedSize.height is less than size.height.

caaVideoDuration :: Lens' CreativeAsset (Maybe Double) Source #

Detected video duration for video asset. This is a read-only field. Applicable to the following creative types: INSTREAM_VIDEO and all VPAID.

caaOriginalBackup :: Lens' CreativeAsset (Maybe Bool) Source #

Whether the backup asset is original or changed by the user in DCM. Applicable to the following creative types: all RICH_MEDIA.

caaWindowMode :: Lens' CreativeAsset (Maybe CreativeAssetWindowMode) Source #

Window mode options for flash assets. Applicable to the following creative types: FLASH_INPAGE, RICH_MEDIA_DISPLAY_EXPANDING, RICH_MEDIA_IM_EXPAND, RICH_MEDIA_DISPLAY_BANNER, and RICH_MEDIA_INPAGE_FLOATING.

caaFlashVersion :: Lens' CreativeAsset (Maybe Int32) Source #

Flash version of the asset. This is a read-only field. Applicable to the following creative types: FLASH_INPAGE, all RICH_MEDIA, and all VPAID. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE.

caaPushdownDuration :: Lens' CreativeAsset (Maybe Double) Source #

Pushdown duration in seconds for an asset. Must be between 0 and 9.99. Applicable to the following creative types: all RICH_MEDIA.Additionally, only applicable when the asset pushdown field is true, the offsets are 0, the collapsedSize.width matches size.width, and the collapsedSize.height is less than size.height.

caaSize :: Lens' CreativeAsset (Maybe Size) Source #

Size associated with this creative asset. This is a required field when applicable; however for IMAGE and FLASH_INPAGE, creatives if left blank, this field will be automatically set using the actual size of the associated image asset. Applicable to the following creative types: DISPLAY_IMAGE_GALLERY, FLASH_INPAGE, HTML5_BANNER, IMAGE, and all RICH_MEDIA. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE.

caaVerticallyLocked :: Lens' CreativeAsset (Maybe Bool) Source #

Whether the asset is vertically locked. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA.

caaOffSet :: Lens' CreativeAsset (Maybe OffSetPosition) Source #

Offset position for an asset in collapsed mode. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA and all VPAID. Additionally, only applicable to assets whose displayType is ASSET_DISPLAY_TYPE_EXPANDING or ASSET_DISPLAY_TYPE_PEEL_DOWN.

caaStreamingServingURL :: Lens' CreativeAsset (Maybe Text) Source #

Streaming URL for video asset. This is a read-only field. Applicable to the following creative types: INSTREAM_VIDEO and all VPAID.

caaZipFilesize :: Lens' CreativeAsset (Maybe Text) Source #

Size of zip file. This is a read-only field. Applicable to the following creative types: HTML5_BANNER.

caaTransparency :: Lens' CreativeAsset (Maybe Bool) Source #

Whether the asset is transparent. Applicable to the following creative types: all RICH_MEDIA. Additionally, only applicable to HTML5 assets.

caaHideSelectionBoxes :: Lens' CreativeAsset (Maybe Bool) Source #

Whether to hide selection boxes flag for an asset. Applicable to the following creative types: all RICH_MEDIA.

caaSSLCompliant :: Lens' CreativeAsset (Maybe Bool) Source #

Whether the asset is SSL-compliant. This is a read-only field. Applicable to all but the following creative types: all REDIRECT and TRACKING_TEXT.

caaFileSize :: Lens' CreativeAsset (Maybe Int64) Source #

File size associated with this creative asset. This is a read-only field. Applicable to all but the following creative types: all REDIRECT and TRACKING_TEXT.

caaAssetIdentifier :: Lens' CreativeAsset (Maybe CreativeAssetId) Source #

Identifier of this asset. This is the same identifier returned during creative asset insert operation. This is a required field. Applicable to all but the following creative types: all REDIRECT and TRACKING_TEXT.

caaDurationType :: Lens' CreativeAsset (Maybe CreativeAssetDurationType) Source #

Duration type for which an asset will be displayed. Applicable to the following creative types: all RICH_MEDIA.

caaProgressiveServingURL :: Lens' CreativeAsset (Maybe Text) Source #

Progressive URL for video asset. This is a read-only field. Applicable to the following creative types: INSTREAM_VIDEO and all VPAID.

caaActive :: Lens' CreativeAsset (Maybe Bool) Source #

Whether the video asset is active. This is a read-only field for VPAID_NON_LINEAR_VIDEO assets. Applicable to the following creative types: INSTREAM_VIDEO and all VPAID.

caaRole :: Lens' CreativeAsset (Maybe CreativeAssetRole) Source #

Role of the asset in relation to creative. Applicable to all but the following creative types: all REDIRECT and TRACKING_TEXT. This is a required field. PRIMARY applies to DISPLAY, FLASH_INPAGE, HTML5_BANNER, IMAGE, DISPLAY_IMAGE_GALLERY, all RICH_MEDIA (which may contain multiple primary assets), and all VPAID creatives. BACKUP_IMAGE applies to FLASH_INPAGE, HTML5_BANNER, all RICH_MEDIA, and all VPAID creatives. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE. ADDITIONAL_IMAGE and ADDITIONAL_FLASH apply to FLASH_INPAGE creatives. OTHER refers to assets from sources other than DCM, such as Studio uploaded assets, applicable to all RICH_MEDIA and all VPAID creatives. PARENT_VIDEO refers to videos uploaded by the user in DCM and is applicable to INSTREAM_VIDEO and VPAID_LINEAR_VIDEO creatives. TRANSCODED_VIDEO refers to videos transcoded by DCM from PARENT_VIDEO assets and is applicable to INSTREAM_VIDEO and VPAID_LINEAR_VIDEO creatives. ALTERNATE_VIDEO refers to the DCM representation of child asset videos from Studio, and is applicable to VPAID_LINEAR_VIDEO creatives. These cannot be added or removed within DCM. For VPAID_LINEAR_VIDEO creatives, PARENT_VIDEO, TRANSCODED_VIDEO and ALTERNATE_VIDEO assets that are marked active serve as backup in case the VPAID creative cannot be served. Only PARENT_VIDEO assets can be added or removed for an INSTREAM_VIDEO or VPAID_LINEAR_VIDEO creative.

caaMimeType :: Lens' CreativeAsset (Maybe Text) Source #

Detected MIME type for video asset. This is a read-only field. Applicable to the following creative types: INSTREAM_VIDEO and all VPAID.

caaPositionTopUnit :: Lens' CreativeAsset (Maybe CreativeAssetPositionTopUnit) Source #

Offset top unit for an asset. This is a read-only field if the asset displayType is ASSET_DISPLAY_TYPE_OVERLAY. Applicable to the following creative types: all RICH_MEDIA.

caaPositionLeftUnit :: Lens' CreativeAsset (Maybe CreativeAssetPositionLeftUnit) Source #

Offset left unit for an asset. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA.

caaAlignment :: Lens' CreativeAsset (Maybe CreativeAssetAlignment) Source #

Possible alignments for an asset. This is a read-only field. Applicable to the following creative types: RICH_MEDIA_DISPLAY_MULTI_FLOATING_INTERSTITIAL.

caaExpandedDimension :: Lens' CreativeAsset (Maybe Size) Source #

Detected expanded dimension for video asset. This is a read-only field. Applicable to the following creative types: INSTREAM_VIDEO and all VPAID.

caaZipFilename :: Lens' CreativeAsset (Maybe Text) Source #

File name of zip file. This is a read-only field. Applicable to the following creative types: HTML5_BANNER.

caaActionScript3 :: Lens' CreativeAsset (Maybe Bool) Source #

Whether ActionScript3 is enabled for the flash asset. This is a read-only field. Applicable to the following creative type: FLASH_INPAGE. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE.

caaDisplayType :: Lens' CreativeAsset (Maybe CreativeAssetDisplayType) Source #

Type of rich media asset. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA.

caaChildAssetType :: Lens' CreativeAsset (Maybe CreativeAssetChildAssetType) Source #

Rich media child asset type. This is a read-only field. Applicable to the following creative types: all VPAID.

caaCollapsedSize :: Lens' CreativeAsset (Maybe Size) Source #

Size of an asset when collapsed. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA and all VPAID. Additionally, applicable to assets whose displayType is ASSET_DISPLAY_TYPE_EXPANDING or ASSET_DISPLAY_TYPE_PEEL_DOWN.

caaId :: Lens' CreativeAsset (Maybe Int64) Source #

Numeric ID of this creative asset. This is a required field and should not be modified. Applicable to all but the following creative types: all REDIRECT and TRACKING_TEXT.

caaBitRate :: Lens' CreativeAsset (Maybe Int32) Source #

Detected bit-rate for video asset. This is a read-only field. Applicable to the following creative types: INSTREAM_VIDEO and all VPAID.

caaCustomStartTimeValue :: Lens' CreativeAsset (Maybe Int32) Source #

Custom start time in seconds for making the asset visible. Applicable to the following creative types: all RICH_MEDIA.

caaStartTimeType :: Lens' CreativeAsset (Maybe CreativeAssetStartTimeType) Source #

Initial wait time type before making the asset visible. Applicable to the following creative types: all RICH_MEDIA.

caaDuration :: Lens' CreativeAsset (Maybe Int32) Source #

Duration in seconds for which an asset will be displayed. Applicable to the following creative types: INSTREAM_VIDEO and VPAID_LINEAR_VIDEO.

caaArtworkType :: Lens' CreativeAsset (Maybe CreativeAssetArtworkType) Source #

Artwork type of rich media creative. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA.

caaHideFlashObjects :: Lens' CreativeAsset (Maybe Bool) Source #

Whether to hide Flash objects flag for an asset. Applicable to the following creative types: all RICH_MEDIA.

caaDetectedFeatures :: Lens' CreativeAsset [CreativeAssetDetectedFeaturesItem] Source #

List of feature dependencies for the creative asset that are detected by DCM. Feature dependencies are features that a browser must be able to support in order to render your HTML5 creative correctly. This is a read-only, auto-generated field. Applicable to the following creative types: HTML5_BANNER. Applicable to DISPLAY when the primary asset type is not HTML_IMAGE.

caaBackupImageExit :: Lens' CreativeAsset (Maybe CreativeCustomEvent) Source #

Exit event configured for the backup image. Applicable to the following creative types: all RICH_MEDIA.

caaPosition :: Lens' CreativeAsset (Maybe OffSetPosition) Source #

Offset position for an asset. Applicable to the following creative types: all RICH_MEDIA.

caaHorizontallyLocked :: Lens' CreativeAsset (Maybe Bool) Source #

Whether the asset is horizontally locked. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA.

AdCompatibility

data AdCompatibility Source #

Compatibility of this ad. Applicable when type is AD_SERVING_DEFAULT_AD. DISPLAY and DISPLAY_INTERSTITIAL refer to either rendering on desktop or on mobile devices or in mobile apps for regular or interstitial ads, respectively. APP and APP_INTERSTITIAL are only used for existing default ads. New mobile placements must be assigned DISPLAY or DISPLAY_INTERSTITIAL and default ads created for those placements will be limited to those compatibility types. IN_STREAM_VIDEO refers to rendering in-stream video ads developed with the VAST standard.

Constructors

ACApp
APP
ACAppInterstitial
APP_INTERSTITIAL
ACDisplay
DISPLAY
ACDisplayInterstitial
DISPLAY_INTERSTITIAL
ACInStreamVideo
IN_STREAM_VIDEO

Instances

Enum AdCompatibility Source # 
Eq AdCompatibility Source # 
Data AdCompatibility Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdCompatibility -> c AdCompatibility #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdCompatibility #

toConstr :: AdCompatibility -> Constr #

dataTypeOf :: AdCompatibility -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdCompatibility) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdCompatibility) #

gmapT :: (forall b. Data b => b -> b) -> AdCompatibility -> AdCompatibility #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdCompatibility -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdCompatibility -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdCompatibility -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdCompatibility -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdCompatibility -> m AdCompatibility #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdCompatibility -> m AdCompatibility #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdCompatibility -> m AdCompatibility #

Ord AdCompatibility Source # 
Read AdCompatibility Source # 
Show AdCompatibility Source # 
Generic AdCompatibility Source # 
Hashable AdCompatibility Source # 
ToJSON AdCompatibility Source # 
FromJSON AdCompatibility Source # 
FromHttpApiData AdCompatibility Source # 
ToHttpApiData AdCompatibility Source # 
type Rep AdCompatibility Source # 
type Rep AdCompatibility = D1 (MetaData "AdCompatibility" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "ACApp" PrefixI False) U1) (C1 (MetaCons "ACAppInterstitial" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ACDisplay" PrefixI False) U1) ((:+:) (C1 (MetaCons "ACDisplayInterstitial" PrefixI False) U1) (C1 (MetaCons "ACInStreamVideo" PrefixI False) U1))))

CreativeFieldValuesListSortField

data CreativeFieldValuesListSortField Source #

Field by which to sort the list.

Constructors

CFVLSFID
ID
CFVLSFValue
VALUE

Instances

Enum CreativeFieldValuesListSortField Source # 
Eq CreativeFieldValuesListSortField Source # 
Data CreativeFieldValuesListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeFieldValuesListSortField -> c CreativeFieldValuesListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeFieldValuesListSortField #

toConstr :: CreativeFieldValuesListSortField -> Constr #

dataTypeOf :: CreativeFieldValuesListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeFieldValuesListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeFieldValuesListSortField) #

gmapT :: (forall b. Data b => b -> b) -> CreativeFieldValuesListSortField -> CreativeFieldValuesListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeFieldValuesListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeFieldValuesListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeFieldValuesListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeFieldValuesListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeFieldValuesListSortField -> m CreativeFieldValuesListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeFieldValuesListSortField -> m CreativeFieldValuesListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeFieldValuesListSortField -> m CreativeFieldValuesListSortField #

Ord CreativeFieldValuesListSortField Source # 
Read CreativeFieldValuesListSortField Source # 
Show CreativeFieldValuesListSortField Source # 
Generic CreativeFieldValuesListSortField Source # 
Hashable CreativeFieldValuesListSortField Source # 
ToJSON CreativeFieldValuesListSortField Source # 
FromJSON CreativeFieldValuesListSortField Source # 
FromHttpApiData CreativeFieldValuesListSortField Source # 
ToHttpApiData CreativeFieldValuesListSortField Source # 
type Rep CreativeFieldValuesListSortField Source # 
type Rep CreativeFieldValuesListSortField = D1 (MetaData "CreativeFieldValuesListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CFVLSFID" PrefixI False) U1) (C1 (MetaCons "CFVLSFValue" PrefixI False) U1))

PlacementsListResponse

data PlacementsListResponse Source #

Placement List Response

See: placementsListResponse smart constructor.

Instances

Eq PlacementsListResponse Source # 
Data PlacementsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementsListResponse -> c PlacementsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementsListResponse #

toConstr :: PlacementsListResponse -> Constr #

dataTypeOf :: PlacementsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> PlacementsListResponse -> PlacementsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementsListResponse -> m PlacementsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementsListResponse -> m PlacementsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementsListResponse -> m PlacementsListResponse #

Show PlacementsListResponse Source # 
Generic PlacementsListResponse Source # 
ToJSON PlacementsListResponse Source # 
FromJSON PlacementsListResponse Source # 
type Rep PlacementsListResponse Source # 
type Rep PlacementsListResponse = D1 (MetaData "PlacementsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PlacementsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_plaNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_plaKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_plaPlacements") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Placement]))))))

placementsListResponse :: PlacementsListResponse Source #

Creates a value of PlacementsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

plaNextPageToken :: Lens' PlacementsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

plaKind :: Lens' PlacementsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#placementsListResponse".

FloodlightActivityGroupsListSortField

data FloodlightActivityGroupsListSortField Source #

Field by which to sort the list.

Constructors

FAGLSFID
ID
FAGLSFName
NAME

Instances

Enum FloodlightActivityGroupsListSortField Source # 
Eq FloodlightActivityGroupsListSortField Source # 
Data FloodlightActivityGroupsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivityGroupsListSortField -> c FloodlightActivityGroupsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivityGroupsListSortField #

toConstr :: FloodlightActivityGroupsListSortField -> Constr #

dataTypeOf :: FloodlightActivityGroupsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivityGroupsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivityGroupsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivityGroupsListSortField -> FloodlightActivityGroupsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityGroupsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityGroupsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivityGroupsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivityGroupsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupsListSortField -> m FloodlightActivityGroupsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupsListSortField -> m FloodlightActivityGroupsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityGroupsListSortField -> m FloodlightActivityGroupsListSortField #

Ord FloodlightActivityGroupsListSortField Source # 
Read FloodlightActivityGroupsListSortField Source # 
Show FloodlightActivityGroupsListSortField Source # 
Generic FloodlightActivityGroupsListSortField Source # 
Hashable FloodlightActivityGroupsListSortField Source # 
ToJSON FloodlightActivityGroupsListSortField Source # 
FromJSON FloodlightActivityGroupsListSortField Source # 
FromHttpApiData FloodlightActivityGroupsListSortField Source # 
ToHttpApiData FloodlightActivityGroupsListSortField Source # 
type Rep FloodlightActivityGroupsListSortField Source # 
type Rep FloodlightActivityGroupsListSortField = D1 (MetaData "FloodlightActivityGroupsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "FAGLSFID" PrefixI False) U1) (C1 (MetaCons "FAGLSFName" PrefixI False) U1))

OrdersListSortOrder

data OrdersListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

OLSOAscending
ASCENDING
OLSODescending
DESCENDING

Instances

Enum OrdersListSortOrder Source # 
Eq OrdersListSortOrder Source # 
Data OrdersListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrdersListSortOrder -> c OrdersListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrdersListSortOrder #

toConstr :: OrdersListSortOrder -> Constr #

dataTypeOf :: OrdersListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrdersListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrdersListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> OrdersListSortOrder -> OrdersListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrdersListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrdersListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrdersListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrdersListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrdersListSortOrder -> m OrdersListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrdersListSortOrder -> m OrdersListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrdersListSortOrder -> m OrdersListSortOrder #

Ord OrdersListSortOrder Source # 
Read OrdersListSortOrder Source # 
Show OrdersListSortOrder Source # 
Generic OrdersListSortOrder Source # 
Hashable OrdersListSortOrder Source # 
ToJSON OrdersListSortOrder Source # 
FromJSON OrdersListSortOrder Source # 
FromHttpApiData OrdersListSortOrder Source # 
ToHttpApiData OrdersListSortOrder Source # 
type Rep OrdersListSortOrder Source # 
type Rep OrdersListSortOrder = D1 (MetaData "OrdersListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "OLSOAscending" PrefixI False) U1) (C1 (MetaCons "OLSODescending" PrefixI False) U1))

ReportSchedule

data ReportSchedule Source #

The report's schedule. Can only be set if the report's 'dateRange' is a relative date range and the relative date range is not "TODAY".

See: reportSchedule smart constructor.

Instances

Eq ReportSchedule Source # 
Data ReportSchedule Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportSchedule -> c ReportSchedule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportSchedule #

toConstr :: ReportSchedule -> Constr #

dataTypeOf :: ReportSchedule -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportSchedule) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportSchedule) #

gmapT :: (forall b. Data b => b -> b) -> ReportSchedule -> ReportSchedule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportSchedule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportSchedule -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportSchedule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportSchedule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportSchedule -> m ReportSchedule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportSchedule -> m ReportSchedule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportSchedule -> m ReportSchedule #

Show ReportSchedule Source # 
Generic ReportSchedule Source # 

Associated Types

type Rep ReportSchedule :: * -> * #

ToJSON ReportSchedule Source # 
FromJSON ReportSchedule Source # 
type Rep ReportSchedule Source # 

reportSchedule :: ReportSchedule Source #

Creates a value of ReportSchedule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rsEvery :: Lens' ReportSchedule (Maybe Int32) Source #

Defines every how many days, weeks or months the report should be run. Needs to be set when "repeats" is either "DAILY", "WEEKLY" or "MONTHLY".

rsActive :: Lens' ReportSchedule (Maybe Bool) Source #

Whether the schedule is active or not. Must be set to either true or false.

rsRepeats :: Lens' ReportSchedule (Maybe Text) Source #

The interval for which the report is repeated. Note: - "DAILY" also requires field "every" to be set. - "WEEKLY" also requires fields "every" and "repeatsOnWeekDays" to be set. - "MONTHLY" also requires fields "every" and "runsOnDayOfMonth" to be set.

rsStartDate :: Lens' ReportSchedule (Maybe Day) Source #

Start date of date range for which scheduled reports should be run.

rsExpirationDate :: Lens' ReportSchedule (Maybe Day) Source #

The expiration date when the scheduled report stops running.

rsRunsOnDayOfMonth :: Lens' ReportSchedule (Maybe ReportScheduleRunsOnDayOfMonth) Source #

Enum to define for "MONTHLY" scheduled reports whether reports should be repeated on the same day of the month as "startDate" or the same day of the week of the month. Example: If 'startDate' is Monday, April 2nd 2012 (2012-04-02), "DAY_OF_MONTH" would run subsequent reports on the 2nd of every Month, and "WEEK_OF_MONTH" would run subsequent reports on the first Monday of the month.

rsRepeatsOnWeekDays :: Lens' ReportSchedule [ReportScheduleRepeatsOnWeekDaysItem] Source #

List of week days "WEEKLY" on which scheduled reports should run.

ReportPathToConversionCriteria

data ReportPathToConversionCriteria Source #

The report criteria for a report of type "PATH_TO_CONVERSION".

See: reportPathToConversionCriteria smart constructor.

Instances

Eq ReportPathToConversionCriteria Source # 
Data ReportPathToConversionCriteria Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportPathToConversionCriteria -> c ReportPathToConversionCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportPathToConversionCriteria #

toConstr :: ReportPathToConversionCriteria -> Constr #

dataTypeOf :: ReportPathToConversionCriteria -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportPathToConversionCriteria) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportPathToConversionCriteria) #

gmapT :: (forall b. Data b => b -> b) -> ReportPathToConversionCriteria -> ReportPathToConversionCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportPathToConversionCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportPathToConversionCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportPathToConversionCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportPathToConversionCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportPathToConversionCriteria -> m ReportPathToConversionCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportPathToConversionCriteria -> m ReportPathToConversionCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportPathToConversionCriteria -> m ReportPathToConversionCriteria #

Show ReportPathToConversionCriteria Source # 
Generic ReportPathToConversionCriteria Source # 
ToJSON ReportPathToConversionCriteria Source # 
FromJSON ReportPathToConversionCriteria Source # 
type Rep ReportPathToConversionCriteria Source # 
type Rep ReportPathToConversionCriteria = D1 (MetaData "ReportPathToConversionCriteria" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ReportPathToConversionCriteria'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rptccReportProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportPathToConversionCriteriaReportProperties))) (S1 (MetaSel (Just Symbol "_rptccMetricNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))) ((:*:) (S1 (MetaSel (Just Symbol "_rptccCustomRichMediaEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DimensionValue]))) (S1 (MetaSel (Just Symbol "_rptccDateRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateRange))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rptccConversionDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SortedDimension]))) (S1 (MetaSel (Just Symbol "_rptccCustomFloodlightVariables") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SortedDimension])))) ((:*:) (S1 (MetaSel (Just Symbol "_rptccFloodlightConfigId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) ((:*:) (S1 (MetaSel (Just Symbol "_rptccActivityFilters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DimensionValue]))) (S1 (MetaSel (Just Symbol "_rptccPerInteractionDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SortedDimension]))))))))

rptccMetricNames :: Lens' ReportPathToConversionCriteria [Text] Source #

The list of names of metrics the report should include.

rptccCustomRichMediaEvents :: Lens' ReportPathToConversionCriteria [DimensionValue] Source #

The list of custom rich media events to include.

rptccDateRange :: Lens' ReportPathToConversionCriteria (Maybe DateRange) Source #

The date range this report should be run for.

rptccConversionDimensions :: Lens' ReportPathToConversionCriteria [SortedDimension] Source #

The list of conversion dimensions the report should include.

rptccCustomFloodlightVariables :: Lens' ReportPathToConversionCriteria [SortedDimension] Source #

The list of custom floodlight variables the report should include.

rptccFloodlightConfigId :: Lens' ReportPathToConversionCriteria (Maybe DimensionValue) Source #

The floodlight ID for which to show data in this report. All advertisers associated with that ID will automatically be added. The dimension of the value needs to be 'dfa:floodlightConfigId'.

rptccActivityFilters :: Lens' ReportPathToConversionCriteria [DimensionValue] Source #

The list of 'dfa:activity' values to filter on.

rptccPerInteractionDimensions :: Lens' ReportPathToConversionCriteria [SortedDimension] Source #

The list of per interaction dimensions the report should include.

MetrosListResponse

data MetrosListResponse Source #

Metro List Response

See: metrosListResponse smart constructor.

Instances

Eq MetrosListResponse Source # 
Data MetrosListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetrosListResponse -> c MetrosListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetrosListResponse #

toConstr :: MetrosListResponse -> Constr #

dataTypeOf :: MetrosListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MetrosListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetrosListResponse) #

gmapT :: (forall b. Data b => b -> b) -> MetrosListResponse -> MetrosListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetrosListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetrosListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetrosListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetrosListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetrosListResponse -> m MetrosListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetrosListResponse -> m MetrosListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetrosListResponse -> m MetrosListResponse #

Show MetrosListResponse Source # 
Generic MetrosListResponse Source # 
ToJSON MetrosListResponse Source # 
FromJSON MetrosListResponse Source # 
type Rep MetrosListResponse Source # 
type Rep MetrosListResponse = D1 (MetaData "MetrosListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "MetrosListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_mlrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_mlrMetros") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Metro])))))

metrosListResponse :: MetrosListResponse Source #

Creates a value of MetrosListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

mlrKind :: Lens' MetrosListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#metrosListResponse".

AccountAccountProFile

data AccountAccountProFile Source #

Profile for this account. This is a read-only field that can be left blank.

Constructors

AccountProFileBasic
ACCOUNT_PROFILE_BASIC
AccountProFileStandard
ACCOUNT_PROFILE_STANDARD

Instances

Enum AccountAccountProFile Source # 
Eq AccountAccountProFile Source # 
Data AccountAccountProFile Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountAccountProFile -> c AccountAccountProFile #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountAccountProFile #

toConstr :: AccountAccountProFile -> Constr #

dataTypeOf :: AccountAccountProFile -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountAccountProFile) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountAccountProFile) #

gmapT :: (forall b. Data b => b -> b) -> AccountAccountProFile -> AccountAccountProFile #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountAccountProFile -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountAccountProFile -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountAccountProFile -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountAccountProFile -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountAccountProFile -> m AccountAccountProFile #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountAccountProFile -> m AccountAccountProFile #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountAccountProFile -> m AccountAccountProFile #

Ord AccountAccountProFile Source # 
Read AccountAccountProFile Source # 
Show AccountAccountProFile Source # 
Generic AccountAccountProFile Source # 
Hashable AccountAccountProFile Source # 
ToJSON AccountAccountProFile Source # 
FromJSON AccountAccountProFile Source # 
FromHttpApiData AccountAccountProFile Source # 
ToHttpApiData AccountAccountProFile Source # 
type Rep AccountAccountProFile Source # 
type Rep AccountAccountProFile = D1 (MetaData "AccountAccountProFile" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "AccountProFileBasic" PrefixI False) U1) (C1 (MetaCons "AccountProFileStandard" PrefixI False) U1))

ConversionsBatchInsertResponse

data ConversionsBatchInsertResponse Source #

Insert Conversions Response.

See: conversionsBatchInsertResponse smart constructor.

Instances

Eq ConversionsBatchInsertResponse Source # 
Data ConversionsBatchInsertResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConversionsBatchInsertResponse -> c ConversionsBatchInsertResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConversionsBatchInsertResponse #

toConstr :: ConversionsBatchInsertResponse -> Constr #

dataTypeOf :: ConversionsBatchInsertResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConversionsBatchInsertResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConversionsBatchInsertResponse) #

gmapT :: (forall b. Data b => b -> b) -> ConversionsBatchInsertResponse -> ConversionsBatchInsertResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConversionsBatchInsertResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConversionsBatchInsertResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConversionsBatchInsertResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConversionsBatchInsertResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConversionsBatchInsertResponse -> m ConversionsBatchInsertResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConversionsBatchInsertResponse -> m ConversionsBatchInsertResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConversionsBatchInsertResponse -> m ConversionsBatchInsertResponse #

Show ConversionsBatchInsertResponse Source # 
Generic ConversionsBatchInsertResponse Source # 
ToJSON ConversionsBatchInsertResponse Source # 
FromJSON ConversionsBatchInsertResponse Source # 
type Rep ConversionsBatchInsertResponse Source # 
type Rep ConversionsBatchInsertResponse = D1 (MetaData "ConversionsBatchInsertResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ConversionsBatchInsertResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cbirbStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ConversionStatus]))) ((:*:) (S1 (MetaSel (Just Symbol "_cbirbKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_cbirbHasFailures") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

conversionsBatchInsertResponse :: ConversionsBatchInsertResponse Source #

Creates a value of ConversionsBatchInsertResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cbirbStatus :: Lens' ConversionsBatchInsertResponse [ConversionStatus] Source #

The status of each conversion's insertion status. The status is returned in the same order that conversions are inserted.

cbirbKind :: Lens' ConversionsBatchInsertResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#conversionsBatchInsertResponse".

cbirbHasFailures :: Lens' ConversionsBatchInsertResponse (Maybe Bool) Source #

Indicates that some or all conversions failed to insert.

OrderDocumentsListResponse

data OrderDocumentsListResponse Source #

Order document List Response

See: orderDocumentsListResponse smart constructor.

Instances

Eq OrderDocumentsListResponse Source # 
Data OrderDocumentsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderDocumentsListResponse -> c OrderDocumentsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderDocumentsListResponse #

toConstr :: OrderDocumentsListResponse -> Constr #

dataTypeOf :: OrderDocumentsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderDocumentsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderDocumentsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> OrderDocumentsListResponse -> OrderDocumentsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderDocumentsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderDocumentsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderDocumentsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderDocumentsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderDocumentsListResponse -> m OrderDocumentsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderDocumentsListResponse -> m OrderDocumentsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderDocumentsListResponse -> m OrderDocumentsListResponse #

Show OrderDocumentsListResponse Source # 
Generic OrderDocumentsListResponse Source # 
ToJSON OrderDocumentsListResponse Source # 
FromJSON OrderDocumentsListResponse Source # 
type Rep OrderDocumentsListResponse Source # 
type Rep OrderDocumentsListResponse = D1 (MetaData "OrderDocumentsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "OrderDocumentsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_odlrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_odlrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_odlrOrderDocuments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [OrderDocument]))))))

orderDocumentsListResponse :: OrderDocumentsListResponse Source #

Creates a value of OrderDocumentsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

odlrNextPageToken :: Lens' OrderDocumentsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

odlrKind :: Lens' OrderDocumentsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#orderDocumentsListResponse".

Recipient

data Recipient Source #

Represents a recipient.

See: recipient smart constructor.

Instances

Eq Recipient Source # 
Data Recipient Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Recipient -> c Recipient #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Recipient #

toConstr :: Recipient -> Constr #

dataTypeOf :: Recipient -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Recipient) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Recipient) #

gmapT :: (forall b. Data b => b -> b) -> Recipient -> Recipient #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Recipient -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Recipient -> r #

gmapQ :: (forall d. Data d => d -> u) -> Recipient -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Recipient -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Recipient -> m Recipient #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Recipient -> m Recipient #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Recipient -> m Recipient #

Show Recipient Source # 
Generic Recipient Source # 

Associated Types

type Rep Recipient :: * -> * #

ToJSON Recipient Source # 
FromJSON Recipient Source # 
type Rep Recipient Source # 
type Rep Recipient = D1 (MetaData "Recipient" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Recipient'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_recEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_recKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_recDeliveryType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RecipientDeliveryType))))))

recipient :: Recipient Source #

Creates a value of Recipient with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

recEmail :: Lens' Recipient (Maybe Text) Source #

The email address of the recipient.

recKind :: Lens' Recipient Text Source #

The kind of resource this is, in this case dfareporting#recipient.

recDeliveryType :: Lens' Recipient (Maybe RecipientDeliveryType) Source #

The delivery type for the recipient.

CreativeType

data CreativeType Source #

Type of this creative.This is a required field. Applicable to all creative types.

Constructors

CTBrandSafeDefaultInstreamVideo
BRAND_SAFE_DEFAULT_INSTREAM_VIDEO
CTCustomDisplay
CUSTOM_DISPLAY
CTCustomDisplayInterstitial
CUSTOM_DISPLAY_INTERSTITIAL
CTDisplay
DISPLAY
CTDisplayImageGallery
DISPLAY_IMAGE_GALLERY
CTDisplayRedirect
DISPLAY_REDIRECT
CTFlashInpage
FLASH_INPAGE
CTHTML5Banner
HTML5_BANNER
CTImage
IMAGE
CTInstreamVideo
INSTREAM_VIDEO
CTInstreamVideoRedirect
INSTREAM_VIDEO_REDIRECT
CTInternalRedirect
INTERNAL_REDIRECT
CTInterstitialInternalRedirect
INTERSTITIAL_INTERNAL_REDIRECT
CTRichMediaDisplayBanner
RICH_MEDIA_DISPLAY_BANNER
CTRichMediaDisplayExpanding
RICH_MEDIA_DISPLAY_EXPANDING
CTRichMediaDisplayInterstitial
RICH_MEDIA_DISPLAY_INTERSTITIAL
CTRichMediaDisplayMultiFloatingInterstitial
RICH_MEDIA_DISPLAY_MULTI_FLOATING_INTERSTITIAL
CTRichMediaImExpand
RICH_MEDIA_IM_EXPAND
CTRichMediaInpageFloating
RICH_MEDIA_INPAGE_FLOATING
CTRichMediaMobileInApp
RICH_MEDIA_MOBILE_IN_APP
CTRichMediaPeelDown
RICH_MEDIA_PEEL_DOWN
CTTrackingText
TRACKING_TEXT
CTVpaidLinearVideo
VPAID_LINEAR_VIDEO
CTVpaidNonLinearVideo
VPAID_NON_LINEAR_VIDEO

Instances

Enum CreativeType Source # 
Eq CreativeType Source # 
Data CreativeType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeType -> c CreativeType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeType #

toConstr :: CreativeType -> Constr #

dataTypeOf :: CreativeType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeType) #

gmapT :: (forall b. Data b => b -> b) -> CreativeType -> CreativeType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeType -> m CreativeType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeType -> m CreativeType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeType -> m CreativeType #

Ord CreativeType Source # 
Read CreativeType Source # 
Show CreativeType Source # 
Generic CreativeType Source # 

Associated Types

type Rep CreativeType :: * -> * #

Hashable CreativeType Source # 
ToJSON CreativeType Source # 
FromJSON CreativeType Source # 
FromHttpApiData CreativeType Source # 
ToHttpApiData CreativeType Source # 
type Rep CreativeType Source # 
type Rep CreativeType = D1 (MetaData "CreativeType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CTBrandSafeDefaultInstreamVideo" PrefixI False) U1) ((:+:) (C1 (MetaCons "CTCustomDisplay" PrefixI False) U1) (C1 (MetaCons "CTCustomDisplayInterstitial" PrefixI False) U1))) ((:+:) (C1 (MetaCons "CTDisplay" PrefixI False) U1) ((:+:) (C1 (MetaCons "CTDisplayImageGallery" PrefixI False) U1) (C1 (MetaCons "CTDisplayRedirect" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "CTFlashInpage" PrefixI False) U1) ((:+:) (C1 (MetaCons "CTHTML5Banner" PrefixI False) U1) (C1 (MetaCons "CTImage" PrefixI False) U1))) ((:+:) (C1 (MetaCons "CTInstreamVideo" PrefixI False) U1) ((:+:) (C1 (MetaCons "CTInstreamVideoRedirect" PrefixI False) U1) (C1 (MetaCons "CTInternalRedirect" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CTInterstitialInternalRedirect" PrefixI False) U1) ((:+:) (C1 (MetaCons "CTRichMediaDisplayBanner" PrefixI False) U1) (C1 (MetaCons "CTRichMediaDisplayExpanding" PrefixI False) U1))) ((:+:) (C1 (MetaCons "CTRichMediaDisplayInterstitial" PrefixI False) U1) ((:+:) (C1 (MetaCons "CTRichMediaDisplayMultiFloatingInterstitial" PrefixI False) U1) (C1 (MetaCons "CTRichMediaImExpand" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "CTRichMediaInpageFloating" PrefixI False) U1) ((:+:) (C1 (MetaCons "CTRichMediaMobileInApp" PrefixI False) U1) (C1 (MetaCons "CTRichMediaPeelDown" PrefixI False) U1))) ((:+:) (C1 (MetaCons "CTTrackingText" PrefixI False) U1) ((:+:) (C1 (MetaCons "CTVpaidLinearVideo" PrefixI False) U1) (C1 (MetaCons "CTVpaidNonLinearVideo" PrefixI False) U1))))))

FilesListSortOrder

data FilesListSortOrder Source #

Order of sorted results, default is 'DESCENDING'.

Constructors

FLSOAscending

ASCENDING Ascending order.

FLSODescending

DESCENDING Descending order.

Instances

Enum FilesListSortOrder Source # 
Eq FilesListSortOrder Source # 
Data FilesListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FilesListSortOrder -> c FilesListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FilesListSortOrder #

toConstr :: FilesListSortOrder -> Constr #

dataTypeOf :: FilesListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FilesListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilesListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> FilesListSortOrder -> FilesListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FilesListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FilesListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> FilesListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FilesListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FilesListSortOrder -> m FilesListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FilesListSortOrder -> m FilesListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FilesListSortOrder -> m FilesListSortOrder #

Ord FilesListSortOrder Source # 
Read FilesListSortOrder Source # 
Show FilesListSortOrder Source # 
Generic FilesListSortOrder Source # 
Hashable FilesListSortOrder Source # 
ToJSON FilesListSortOrder Source # 
FromJSON FilesListSortOrder Source # 
FromHttpApiData FilesListSortOrder Source # 
ToHttpApiData FilesListSortOrder Source # 
type Rep FilesListSortOrder Source # 
type Rep FilesListSortOrder = D1 (MetaData "FilesListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "FLSOAscending" PrefixI False) U1) (C1 (MetaCons "FLSODescending" PrefixI False) U1))

AdvertiserGroupsListSortField

data AdvertiserGroupsListSortField Source #

Field by which to sort the list.

Constructors

AGLSFID
ID
AGLSFName
NAME

Instances

Enum AdvertiserGroupsListSortField Source # 
Eq AdvertiserGroupsListSortField Source # 
Data AdvertiserGroupsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdvertiserGroupsListSortField -> c AdvertiserGroupsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdvertiserGroupsListSortField #

toConstr :: AdvertiserGroupsListSortField -> Constr #

dataTypeOf :: AdvertiserGroupsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdvertiserGroupsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdvertiserGroupsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> AdvertiserGroupsListSortField -> AdvertiserGroupsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdvertiserGroupsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdvertiserGroupsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdvertiserGroupsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdvertiserGroupsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdvertiserGroupsListSortField -> m AdvertiserGroupsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertiserGroupsListSortField -> m AdvertiserGroupsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertiserGroupsListSortField -> m AdvertiserGroupsListSortField #

Ord AdvertiserGroupsListSortField Source # 
Read AdvertiserGroupsListSortField Source # 
Show AdvertiserGroupsListSortField Source # 
Generic AdvertiserGroupsListSortField Source # 
Hashable AdvertiserGroupsListSortField Source # 
ToJSON AdvertiserGroupsListSortField Source # 
FromJSON AdvertiserGroupsListSortField Source # 
FromHttpApiData AdvertiserGroupsListSortField Source # 
ToHttpApiData AdvertiserGroupsListSortField Source # 
type Rep AdvertiserGroupsListSortField Source # 
type Rep AdvertiserGroupsListSortField = D1 (MetaData "AdvertiserGroupsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "AGLSFID" PrefixI False) U1) (C1 (MetaCons "AGLSFName" PrefixI False) U1))

TargetWindowTargetWindowOption

data TargetWindowTargetWindowOption Source #

Type of browser window for which the backup image of the flash creative can be displayed.

Constructors

CurrentWindow
CURRENT_WINDOW
Custom
CUSTOM
NewWindow
NEW_WINDOW

Instances

Enum TargetWindowTargetWindowOption Source # 
Eq TargetWindowTargetWindowOption Source # 
Data TargetWindowTargetWindowOption Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TargetWindowTargetWindowOption -> c TargetWindowTargetWindowOption #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TargetWindowTargetWindowOption #

toConstr :: TargetWindowTargetWindowOption -> Constr #

dataTypeOf :: TargetWindowTargetWindowOption -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TargetWindowTargetWindowOption) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TargetWindowTargetWindowOption) #

gmapT :: (forall b. Data b => b -> b) -> TargetWindowTargetWindowOption -> TargetWindowTargetWindowOption #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TargetWindowTargetWindowOption -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TargetWindowTargetWindowOption -> r #

gmapQ :: (forall d. Data d => d -> u) -> TargetWindowTargetWindowOption -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TargetWindowTargetWindowOption -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TargetWindowTargetWindowOption -> m TargetWindowTargetWindowOption #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetWindowTargetWindowOption -> m TargetWindowTargetWindowOption #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetWindowTargetWindowOption -> m TargetWindowTargetWindowOption #

Ord TargetWindowTargetWindowOption Source # 
Read TargetWindowTargetWindowOption Source # 
Show TargetWindowTargetWindowOption Source # 
Generic TargetWindowTargetWindowOption Source # 
Hashable TargetWindowTargetWindowOption Source # 
ToJSON TargetWindowTargetWindowOption Source # 
FromJSON TargetWindowTargetWindowOption Source # 
FromHttpApiData TargetWindowTargetWindowOption Source # 
ToHttpApiData TargetWindowTargetWindowOption Source # 
type Rep TargetWindowTargetWindowOption Source # 
type Rep TargetWindowTargetWindowOption = D1 (MetaData "TargetWindowTargetWindowOption" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CurrentWindow" PrefixI False) U1) ((:+:) (C1 (MetaCons "Custom" PrefixI False) U1) (C1 (MetaCons "NewWindow" PrefixI False) U1)))

DirectorySiteContactsListSortField

data DirectorySiteContactsListSortField Source #

Field by which to sort the list.

Constructors

DSCLSFID
ID
DSCLSFName
NAME

Instances

Enum DirectorySiteContactsListSortField Source # 
Eq DirectorySiteContactsListSortField Source # 
Data DirectorySiteContactsListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectorySiteContactsListSortField -> c DirectorySiteContactsListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectorySiteContactsListSortField #

toConstr :: DirectorySiteContactsListSortField -> Constr #

dataTypeOf :: DirectorySiteContactsListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectorySiteContactsListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectorySiteContactsListSortField) #

gmapT :: (forall b. Data b => b -> b) -> DirectorySiteContactsListSortField -> DirectorySiteContactsListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteContactsListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteContactsListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectorySiteContactsListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectorySiteContactsListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectorySiteContactsListSortField -> m DirectorySiteContactsListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteContactsListSortField -> m DirectorySiteContactsListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteContactsListSortField -> m DirectorySiteContactsListSortField #

Ord DirectorySiteContactsListSortField Source # 
Read DirectorySiteContactsListSortField Source # 
Show DirectorySiteContactsListSortField Source # 
Generic DirectorySiteContactsListSortField Source # 
Hashable DirectorySiteContactsListSortField Source # 
ToJSON DirectorySiteContactsListSortField Source # 
FromJSON DirectorySiteContactsListSortField Source # 
FromHttpApiData DirectorySiteContactsListSortField Source # 
ToHttpApiData DirectorySiteContactsListSortField Source # 
type Rep DirectorySiteContactsListSortField Source # 
type Rep DirectorySiteContactsListSortField = D1 (MetaData "DirectorySiteContactsListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "DSCLSFID" PrefixI False) U1) (C1 (MetaCons "DSCLSFName" PrefixI False) U1))

PlacementsListPricingTypes

data PlacementsListPricingTypes Source #

Select only placements with these pricing types.

Constructors

PLPTPricingTypeCpa
PRICING_TYPE_CPA
PLPTPricingTypeCpc
PRICING_TYPE_CPC
PLPTPricingTypeCpm
PRICING_TYPE_CPM
PLPTPricingTypeFlatRateClicks
PRICING_TYPE_FLAT_RATE_CLICKS
PLPTPricingTypeFlatRateImpressions
PRICING_TYPE_FLAT_RATE_IMPRESSIONS

Instances

Enum PlacementsListPricingTypes Source # 
Eq PlacementsListPricingTypes Source # 
Data PlacementsListPricingTypes Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementsListPricingTypes -> c PlacementsListPricingTypes #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementsListPricingTypes #

toConstr :: PlacementsListPricingTypes -> Constr #

dataTypeOf :: PlacementsListPricingTypes -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementsListPricingTypes) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementsListPricingTypes) #

gmapT :: (forall b. Data b => b -> b) -> PlacementsListPricingTypes -> PlacementsListPricingTypes #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementsListPricingTypes -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementsListPricingTypes -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementsListPricingTypes -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementsListPricingTypes -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementsListPricingTypes -> m PlacementsListPricingTypes #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementsListPricingTypes -> m PlacementsListPricingTypes #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementsListPricingTypes -> m PlacementsListPricingTypes #

Ord PlacementsListPricingTypes Source # 
Read PlacementsListPricingTypes Source # 
Show PlacementsListPricingTypes Source # 
Generic PlacementsListPricingTypes Source # 
Hashable PlacementsListPricingTypes Source # 
ToJSON PlacementsListPricingTypes Source # 
FromJSON PlacementsListPricingTypes Source # 
FromHttpApiData PlacementsListPricingTypes Source # 
ToHttpApiData PlacementsListPricingTypes Source # 
type Rep PlacementsListPricingTypes Source # 
type Rep PlacementsListPricingTypes = D1 (MetaData "PlacementsListPricingTypes" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "PLPTPricingTypeCpa" PrefixI False) U1) (C1 (MetaCons "PLPTPricingTypeCpc" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PLPTPricingTypeCpm" PrefixI False) U1) ((:+:) (C1 (MetaCons "PLPTPricingTypeFlatRateClicks" PrefixI False) U1) (C1 (MetaCons "PLPTPricingTypeFlatRateImpressions" PrefixI False) U1))))

EventTagsListSortOrder

data EventTagsListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

ETLSOAscending
ASCENDING
ETLSODescending
DESCENDING

Instances

Enum EventTagsListSortOrder Source # 
Eq EventTagsListSortOrder Source # 
Data EventTagsListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventTagsListSortOrder -> c EventTagsListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventTagsListSortOrder #

toConstr :: EventTagsListSortOrder -> Constr #

dataTypeOf :: EventTagsListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EventTagsListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventTagsListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> EventTagsListSortOrder -> EventTagsListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventTagsListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventTagsListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventTagsListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventTagsListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventTagsListSortOrder -> m EventTagsListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTagsListSortOrder -> m EventTagsListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTagsListSortOrder -> m EventTagsListSortOrder #

Ord EventTagsListSortOrder Source # 
Read EventTagsListSortOrder Source # 
Show EventTagsListSortOrder Source # 
Generic EventTagsListSortOrder Source # 
Hashable EventTagsListSortOrder Source # 
ToJSON EventTagsListSortOrder Source # 
FromJSON EventTagsListSortOrder Source # 
FromHttpApiData EventTagsListSortOrder Source # 
ToHttpApiData EventTagsListSortOrder Source # 
type Rep EventTagsListSortOrder Source # 
type Rep EventTagsListSortOrder = D1 (MetaData "EventTagsListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ETLSOAscending" PrefixI False) U1) (C1 (MetaCons "ETLSODescending" PrefixI False) U1))

EncryptionInfoEncryptionSource

data EncryptionInfoEncryptionSource Source #

Describes whether the encrypted cookie was received from ad serving (the %m macro) or from Data Transfer.

Constructors

AdServing
AD_SERVING
DataTransfer
DATA_TRANSFER
EncryptionScopeUnknown
ENCRYPTION_SCOPE_UNKNOWN

Instances

Enum EncryptionInfoEncryptionSource Source # 
Eq EncryptionInfoEncryptionSource Source # 
Data EncryptionInfoEncryptionSource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EncryptionInfoEncryptionSource -> c EncryptionInfoEncryptionSource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EncryptionInfoEncryptionSource #

toConstr :: EncryptionInfoEncryptionSource -> Constr #

dataTypeOf :: EncryptionInfoEncryptionSource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EncryptionInfoEncryptionSource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EncryptionInfoEncryptionSource) #

gmapT :: (forall b. Data b => b -> b) -> EncryptionInfoEncryptionSource -> EncryptionInfoEncryptionSource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EncryptionInfoEncryptionSource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EncryptionInfoEncryptionSource -> r #

gmapQ :: (forall d. Data d => d -> u) -> EncryptionInfoEncryptionSource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EncryptionInfoEncryptionSource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EncryptionInfoEncryptionSource -> m EncryptionInfoEncryptionSource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EncryptionInfoEncryptionSource -> m EncryptionInfoEncryptionSource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EncryptionInfoEncryptionSource -> m EncryptionInfoEncryptionSource #

Ord EncryptionInfoEncryptionSource Source # 
Read EncryptionInfoEncryptionSource Source # 
Show EncryptionInfoEncryptionSource Source # 
Generic EncryptionInfoEncryptionSource Source # 
Hashable EncryptionInfoEncryptionSource Source # 
ToJSON EncryptionInfoEncryptionSource Source # 
FromJSON EncryptionInfoEncryptionSource Source # 
FromHttpApiData EncryptionInfoEncryptionSource Source # 
ToHttpApiData EncryptionInfoEncryptionSource Source # 
type Rep EncryptionInfoEncryptionSource Source # 
type Rep EncryptionInfoEncryptionSource = D1 (MetaData "EncryptionInfoEncryptionSource" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "AdServing" PrefixI False) U1) ((:+:) (C1 (MetaCons "DataTransfer" PrefixI False) U1) (C1 (MetaCons "EncryptionScopeUnknown" PrefixI False) U1)))

DirectorySitesListSortField

data DirectorySitesListSortField Source #

Field by which to sort the list.

Constructors

DSLSFID
ID
DSLSFName
NAME

Instances

Enum DirectorySitesListSortField Source # 
Eq DirectorySitesListSortField Source # 
Data DirectorySitesListSortField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectorySitesListSortField -> c DirectorySitesListSortField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectorySitesListSortField #

toConstr :: DirectorySitesListSortField -> Constr #

dataTypeOf :: DirectorySitesListSortField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectorySitesListSortField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectorySitesListSortField) #

gmapT :: (forall b. Data b => b -> b) -> DirectorySitesListSortField -> DirectorySitesListSortField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySitesListSortField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySitesListSortField -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectorySitesListSortField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectorySitesListSortField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectorySitesListSortField -> m DirectorySitesListSortField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySitesListSortField -> m DirectorySitesListSortField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySitesListSortField -> m DirectorySitesListSortField #

Ord DirectorySitesListSortField Source # 
Read DirectorySitesListSortField Source # 
Show DirectorySitesListSortField Source # 
Generic DirectorySitesListSortField Source # 
Hashable DirectorySitesListSortField Source # 
ToJSON DirectorySitesListSortField Source # 
FromJSON DirectorySitesListSortField Source # 
FromHttpApiData DirectorySitesListSortField Source # 
ToHttpApiData DirectorySitesListSortField Source # 
type Rep DirectorySitesListSortField Source # 
type Rep DirectorySitesListSortField = D1 (MetaData "DirectorySitesListSortField" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "DSLSFID" PrefixI False) U1) (C1 (MetaCons "DSLSFName" PrefixI False) U1))

Site

data Site Source #

Contains properties of a site.

See: site smart constructor.

Instances

Eq Site Source # 

Methods

(==) :: Site -> Site -> Bool #

(/=) :: Site -> Site -> Bool #

Data Site Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Site -> c Site #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Site #

toConstr :: Site -> Constr #

dataTypeOf :: Site -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Site) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Site) #

gmapT :: (forall b. Data b => b -> b) -> Site -> Site #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Site -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Site -> r #

gmapQ :: (forall d. Data d => d -> u) -> Site -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Site -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Site -> m Site #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Site -> m Site #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Site -> m Site #

Show Site Source # 

Methods

showsPrec :: Int -> Site -> ShowS #

show :: Site -> String #

showList :: [Site] -> ShowS #

Generic Site Source # 

Associated Types

type Rep Site :: * -> * #

Methods

from :: Site -> Rep Site x #

to :: Rep Site x -> Site #

ToJSON Site Source # 
FromJSON Site Source # 
type Rep Site Source # 
type Rep Site = D1 (MetaData "Site" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Site'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ssKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_ssKeyName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ssSiteContacts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SiteContact]))))) ((:*:) (S1 (MetaSel (Just Symbol "_ssSiteSettings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SiteSettings))) ((:*:) (S1 (MetaSel (Just Symbol "_ssIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_ssDirectorySiteIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ssAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_ssName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ssDirectorySiteId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) (S1 (MetaSel (Just Symbol "_ssId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_ssSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_ssApproved") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))))

site :: Site Source #

Creates a value of Site with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ssKind :: Lens' Site Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#site".

ssKeyName :: Lens' Site (Maybe Text) Source #

Key name of this site. This is a read-only, auto-generated field.

ssIdDimensionValue :: Lens' Site (Maybe DimensionValue) Source #

Dimension value for the ID of this site. This is a read-only, auto-generated field.

ssDirectorySiteIdDimensionValue :: Lens' Site (Maybe DimensionValue) Source #

Dimension value for the ID of the directory site. This is a read-only, auto-generated field.

ssAccountId :: Lens' Site (Maybe Int64) Source #

Account ID of this site. This is a read-only field that can be left blank.

ssName :: Lens' Site (Maybe Text) Source #

Name of this site.This is a required field. Must be less than 128 characters long. If this site is under a subaccount, the name must be unique among sites of the same subaccount. Otherwise, this site is a top-level site, and the name must be unique among top-level sites of the same account.

ssDirectorySiteId :: Lens' Site (Maybe Int64) Source #

Directory site associated with this site. This is a required field that is read-only after insertion.

ssId :: Lens' Site (Maybe Int64) Source #

ID of this site. This is a read-only, auto-generated field.

ssSubAccountId :: Lens' Site (Maybe Int64) Source #

Subaccount ID of this site. This is a read-only field that can be left blank.

ssApproved :: Lens' Site (Maybe Bool) Source #

Whether this site is approved.

ReportCrossDimensionReachCriteriaDimension

data ReportCrossDimensionReachCriteriaDimension Source #

The dimension option.

Constructors

RCDRCDAdvertiser
ADVERTISER
RCDRCDCampaign
CAMPAIGN
RCDRCDSiteByAdvertiser
SITE_BY_ADVERTISER
RCDRCDSiteByCampaign
SITE_BY_CAMPAIGN

Instances

Enum ReportCrossDimensionReachCriteriaDimension Source # 
Eq ReportCrossDimensionReachCriteriaDimension Source # 
Data ReportCrossDimensionReachCriteriaDimension Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportCrossDimensionReachCriteriaDimension -> c ReportCrossDimensionReachCriteriaDimension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportCrossDimensionReachCriteriaDimension #

toConstr :: ReportCrossDimensionReachCriteriaDimension -> Constr #

dataTypeOf :: ReportCrossDimensionReachCriteriaDimension -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportCrossDimensionReachCriteriaDimension) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportCrossDimensionReachCriteriaDimension) #

gmapT :: (forall b. Data b => b -> b) -> ReportCrossDimensionReachCriteriaDimension -> ReportCrossDimensionReachCriteriaDimension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportCrossDimensionReachCriteriaDimension -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportCrossDimensionReachCriteriaDimension -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportCrossDimensionReachCriteriaDimension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportCrossDimensionReachCriteriaDimension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportCrossDimensionReachCriteriaDimension -> m ReportCrossDimensionReachCriteriaDimension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportCrossDimensionReachCriteriaDimension -> m ReportCrossDimensionReachCriteriaDimension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportCrossDimensionReachCriteriaDimension -> m ReportCrossDimensionReachCriteriaDimension #

Ord ReportCrossDimensionReachCriteriaDimension Source # 
Read ReportCrossDimensionReachCriteriaDimension Source # 
Show ReportCrossDimensionReachCriteriaDimension Source # 
Generic ReportCrossDimensionReachCriteriaDimension Source # 
Hashable ReportCrossDimensionReachCriteriaDimension Source # 
ToJSON ReportCrossDimensionReachCriteriaDimension Source # 
FromJSON ReportCrossDimensionReachCriteriaDimension Source # 
FromHttpApiData ReportCrossDimensionReachCriteriaDimension Source # 
ToHttpApiData ReportCrossDimensionReachCriteriaDimension Source # 
type Rep ReportCrossDimensionReachCriteriaDimension Source # 
type Rep ReportCrossDimensionReachCriteriaDimension = D1 (MetaData "ReportCrossDimensionReachCriteriaDimension" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "RCDRCDAdvertiser" PrefixI False) U1) (C1 (MetaCons "RCDRCDCampaign" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RCDRCDSiteByAdvertiser" PrefixI False) U1) (C1 (MetaCons "RCDRCDSiteByCampaign" PrefixI False) U1)))

SitesListSortOrder

data SitesListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

SLSOAscending
ASCENDING
SLSODescending
DESCENDING

Instances

Enum SitesListSortOrder Source # 
Eq SitesListSortOrder Source # 
Data SitesListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SitesListSortOrder -> c SitesListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SitesListSortOrder #

toConstr :: SitesListSortOrder -> Constr #

dataTypeOf :: SitesListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SitesListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SitesListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> SitesListSortOrder -> SitesListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SitesListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SitesListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> SitesListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SitesListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SitesListSortOrder -> m SitesListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SitesListSortOrder -> m SitesListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SitesListSortOrder -> m SitesListSortOrder #

Ord SitesListSortOrder Source # 
Read SitesListSortOrder Source # 
Show SitesListSortOrder Source # 
Generic SitesListSortOrder Source # 
Hashable SitesListSortOrder Source # 
ToJSON SitesListSortOrder Source # 
FromJSON SitesListSortOrder Source # 
FromHttpApiData SitesListSortOrder Source # 
ToHttpApiData SitesListSortOrder Source # 
type Rep SitesListSortOrder Source # 
type Rep SitesListSortOrder = D1 (MetaData "SitesListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "SLSOAscending" PrefixI False) U1) (C1 (MetaCons "SLSODescending" PrefixI False) U1))

UserDefinedVariableConfiguration

data UserDefinedVariableConfiguration Source #

User Defined Variable configuration.

See: userDefinedVariableConfiguration smart constructor.

Instances

Eq UserDefinedVariableConfiguration Source # 
Data UserDefinedVariableConfiguration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserDefinedVariableConfiguration -> c UserDefinedVariableConfiguration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserDefinedVariableConfiguration #

toConstr :: UserDefinedVariableConfiguration -> Constr #

dataTypeOf :: UserDefinedVariableConfiguration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserDefinedVariableConfiguration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserDefinedVariableConfiguration) #

gmapT :: (forall b. Data b => b -> b) -> UserDefinedVariableConfiguration -> UserDefinedVariableConfiguration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserDefinedVariableConfiguration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserDefinedVariableConfiguration -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserDefinedVariableConfiguration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserDefinedVariableConfiguration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserDefinedVariableConfiguration -> m UserDefinedVariableConfiguration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserDefinedVariableConfiguration -> m UserDefinedVariableConfiguration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserDefinedVariableConfiguration -> m UserDefinedVariableConfiguration #

Show UserDefinedVariableConfiguration Source # 
Generic UserDefinedVariableConfiguration Source # 
ToJSON UserDefinedVariableConfiguration Source # 
FromJSON UserDefinedVariableConfiguration Source # 
type Rep UserDefinedVariableConfiguration Source # 
type Rep UserDefinedVariableConfiguration = D1 (MetaData "UserDefinedVariableConfiguration" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "UserDefinedVariableConfiguration'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_udvcReportName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_udvcDataType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UserDefinedVariableConfigurationDataType))) (S1 (MetaSel (Just Symbol "_udvcVariableType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UserDefinedVariableConfigurationVariableType))))))

userDefinedVariableConfiguration :: UserDefinedVariableConfiguration Source #

Creates a value of UserDefinedVariableConfiguration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

udvcReportName :: Lens' UserDefinedVariableConfiguration (Maybe Text) Source #

User-friendly name for the variable which will appear in reports. This is a required field, must be less than 64 characters long, and cannot contain the following characters: ""<>".

ReportCrossDimensionReachCriteria

data ReportCrossDimensionReachCriteria Source #

The report criteria for a report of type "CROSS_DIMENSION_REACH".

See: reportCrossDimensionReachCriteria smart constructor.

Instances

Eq ReportCrossDimensionReachCriteria Source # 
Data ReportCrossDimensionReachCriteria Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportCrossDimensionReachCriteria -> c ReportCrossDimensionReachCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportCrossDimensionReachCriteria #

toConstr :: ReportCrossDimensionReachCriteria -> Constr #

dataTypeOf :: ReportCrossDimensionReachCriteria -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportCrossDimensionReachCriteria) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportCrossDimensionReachCriteria) #

gmapT :: (forall b. Data b => b -> b) -> ReportCrossDimensionReachCriteria -> ReportCrossDimensionReachCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportCrossDimensionReachCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportCrossDimensionReachCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportCrossDimensionReachCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportCrossDimensionReachCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportCrossDimensionReachCriteria -> m ReportCrossDimensionReachCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportCrossDimensionReachCriteria -> m ReportCrossDimensionReachCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportCrossDimensionReachCriteria -> m ReportCrossDimensionReachCriteria #

Show ReportCrossDimensionReachCriteria Source # 
Generic ReportCrossDimensionReachCriteria Source # 
ToJSON ReportCrossDimensionReachCriteria Source # 
FromJSON ReportCrossDimensionReachCriteria Source # 
type Rep ReportCrossDimensionReachCriteria Source # 
type Rep ReportCrossDimensionReachCriteria = D1 (MetaData "ReportCrossDimensionReachCriteria" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ReportCrossDimensionReachCriteria'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcdrcPivoted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_rcdrcBreakdown") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SortedDimension]))) (S1 (MetaSel (Just Symbol "_rcdrcDimension") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReportCrossDimensionReachCriteriaDimension))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcdrcMetricNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_rcdrcDimensionFilters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DimensionValue])))) ((:*:) (S1 (MetaSel (Just Symbol "_rcdrcDateRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateRange))) (S1 (MetaSel (Just Symbol "_rcdrcOverlapMetricNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))))))

rcdrcPivoted :: Lens' ReportCrossDimensionReachCriteria (Maybe Bool) Source #

Whether the report is pivoted or not. Defaults to true.

rcdrcBreakdown :: Lens' ReportCrossDimensionReachCriteria [SortedDimension] Source #

The list of dimensions the report should include.

rcdrcMetricNames :: Lens' ReportCrossDimensionReachCriteria [Text] Source #

The list of names of metrics the report should include.

rcdrcDimensionFilters :: Lens' ReportCrossDimensionReachCriteria [DimensionValue] Source #

The list of filters on which dimensions are filtered.

rcdrcDateRange :: Lens' ReportCrossDimensionReachCriteria (Maybe DateRange) Source #

The date range this report should be run for.

rcdrcOverlapMetricNames :: Lens' ReportCrossDimensionReachCriteria [Text] Source #

The list of names of overlap metrics the report should include.

FileURLs

data FileURLs Source #

The URLs where the completed report file can be downloaded.

See: fileURLs smart constructor.

Instances

Eq FileURLs Source # 
Data FileURLs Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FileURLs -> c FileURLs #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FileURLs #

toConstr :: FileURLs -> Constr #

dataTypeOf :: FileURLs -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FileURLs) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FileURLs) #

gmapT :: (forall b. Data b => b -> b) -> FileURLs -> FileURLs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FileURLs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FileURLs -> r #

gmapQ :: (forall d. Data d => d -> u) -> FileURLs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FileURLs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FileURLs -> m FileURLs #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FileURLs -> m FileURLs #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FileURLs -> m FileURLs #

Show FileURLs Source # 
Generic FileURLs Source # 

Associated Types

type Rep FileURLs :: * -> * #

Methods

from :: FileURLs -> Rep FileURLs x #

to :: Rep FileURLs x -> FileURLs #

ToJSON FileURLs Source # 
FromJSON FileURLs Source # 
type Rep FileURLs Source # 
type Rep FileURLs = D1 (MetaData "FileURLs" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FileURLs'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fuBrowserURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_fuAPIURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

fileURLs :: FileURLs Source #

Creates a value of FileURLs with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

fuBrowserURL :: Lens' FileURLs (Maybe Text) Source #

The URL for downloading the report data through a browser.

fuAPIURL :: Lens' FileURLs (Maybe Text) Source #

The URL for downloading the report data through the API.

CampaignCreativeAssociationsListResponse

data CampaignCreativeAssociationsListResponse Source #

Campaign Creative Association List Response

See: campaignCreativeAssociationsListResponse smart constructor.

Instances

Eq CampaignCreativeAssociationsListResponse Source # 
Data CampaignCreativeAssociationsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CampaignCreativeAssociationsListResponse -> c CampaignCreativeAssociationsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CampaignCreativeAssociationsListResponse #

toConstr :: CampaignCreativeAssociationsListResponse -> Constr #

dataTypeOf :: CampaignCreativeAssociationsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CampaignCreativeAssociationsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CampaignCreativeAssociationsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> CampaignCreativeAssociationsListResponse -> CampaignCreativeAssociationsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CampaignCreativeAssociationsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CampaignCreativeAssociationsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> CampaignCreativeAssociationsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CampaignCreativeAssociationsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CampaignCreativeAssociationsListResponse -> m CampaignCreativeAssociationsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignCreativeAssociationsListResponse -> m CampaignCreativeAssociationsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CampaignCreativeAssociationsListResponse -> m CampaignCreativeAssociationsListResponse #

Show CampaignCreativeAssociationsListResponse Source # 
Generic CampaignCreativeAssociationsListResponse Source # 
ToJSON CampaignCreativeAssociationsListResponse Source # 
FromJSON CampaignCreativeAssociationsListResponse Source # 
type Rep CampaignCreativeAssociationsListResponse Source # 
type Rep CampaignCreativeAssociationsListResponse = D1 (MetaData "CampaignCreativeAssociationsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CampaignCreativeAssociationsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ccalrCampaignCreativeAssociations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CampaignCreativeAssociation]))) ((:*:) (S1 (MetaSel (Just Symbol "_ccalrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ccalrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

campaignCreativeAssociationsListResponse :: CampaignCreativeAssociationsListResponse Source #

Creates a value of CampaignCreativeAssociationsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ccalrNextPageToken :: Lens' CampaignCreativeAssociationsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

ccalrKind :: Lens' CampaignCreativeAssociationsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#campaignCreativeAssociationsListResponse".

PlacementTagFormatsItem

data PlacementTagFormatsItem Source #

Constructors

PTFIPlacementTagClickCommands
PLACEMENT_TAG_CLICK_COMMANDS
PTFIPlacementTagIframeIlayer
PLACEMENT_TAG_IFRAME_ILAYER
PTFIPlacementTagIframeJavascript
PLACEMENT_TAG_IFRAME_JAVASCRIPT
PTFIPlacementTagIframeJavascriptLegacy
PLACEMENT_TAG_IFRAME_JAVASCRIPT_LEGACY
PTFIPlacementTagInstreamVideoPrefetch
PLACEMENT_TAG_INSTREAM_VIDEO_PREFETCH
PTFIPlacementTagInstreamVideoPrefetchVast3
PLACEMENT_TAG_INSTREAM_VIDEO_PREFETCH_VAST_3
PTFIPlacementTagInternalRedirect
PLACEMENT_TAG_INTERNAL_REDIRECT
PTFIPlacementTagInterstitialIframeJavascript
PLACEMENT_TAG_INTERSTITIAL_IFRAME_JAVASCRIPT
PTFIPlacementTagInterstitialIframeJavascriptLegacy
PLACEMENT_TAG_INTERSTITIAL_IFRAME_JAVASCRIPT_LEGACY
PTFIPlacementTagInterstitialInternalRedirect
PLACEMENT_TAG_INTERSTITIAL_INTERNAL_REDIRECT
PTFIPlacementTagInterstitialJavascript
PLACEMENT_TAG_INTERSTITIAL_JAVASCRIPT
PTFIPlacementTagInterstitialJavascriptLegacy
PLACEMENT_TAG_INTERSTITIAL_JAVASCRIPT_LEGACY
PTFIPlacementTagJavascript
PLACEMENT_TAG_JAVASCRIPT
PTFIPlacementTagJavascriptLegacy
PLACEMENT_TAG_JAVASCRIPT_LEGACY
PTFIPlacementTagStandard
PLACEMENT_TAG_STANDARD
PTFIPlacementTagTracking
PLACEMENT_TAG_TRACKING
PTFIPlacementTagTrackingIframe
PLACEMENT_TAG_TRACKING_IFRAME
PTFIPlacementTagTrackingJavascript
PLACEMENT_TAG_TRACKING_JAVASCRIPT

Instances

Enum PlacementTagFormatsItem Source # 
Eq PlacementTagFormatsItem Source # 
Data PlacementTagFormatsItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementTagFormatsItem -> c PlacementTagFormatsItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementTagFormatsItem #

toConstr :: PlacementTagFormatsItem -> Constr #

dataTypeOf :: PlacementTagFormatsItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementTagFormatsItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementTagFormatsItem) #

gmapT :: (forall b. Data b => b -> b) -> PlacementTagFormatsItem -> PlacementTagFormatsItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementTagFormatsItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementTagFormatsItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementTagFormatsItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementTagFormatsItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementTagFormatsItem -> m PlacementTagFormatsItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementTagFormatsItem -> m PlacementTagFormatsItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementTagFormatsItem -> m PlacementTagFormatsItem #

Ord PlacementTagFormatsItem Source # 
Read PlacementTagFormatsItem Source # 
Show PlacementTagFormatsItem Source # 
Generic PlacementTagFormatsItem Source # 
Hashable PlacementTagFormatsItem Source # 
ToJSON PlacementTagFormatsItem Source # 
FromJSON PlacementTagFormatsItem Source # 
FromHttpApiData PlacementTagFormatsItem Source # 
ToHttpApiData PlacementTagFormatsItem Source # 
type Rep PlacementTagFormatsItem Source # 
type Rep PlacementTagFormatsItem = D1 (MetaData "PlacementTagFormatsItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "PTFIPlacementTagClickCommands" PrefixI False) U1) (C1 (MetaCons "PTFIPlacementTagIframeIlayer" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PTFIPlacementTagIframeJavascript" PrefixI False) U1) (C1 (MetaCons "PTFIPlacementTagIframeJavascriptLegacy" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PTFIPlacementTagInstreamVideoPrefetch" PrefixI False) U1) (C1 (MetaCons "PTFIPlacementTagInstreamVideoPrefetchVast3" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PTFIPlacementTagInternalRedirect" PrefixI False) U1) ((:+:) (C1 (MetaCons "PTFIPlacementTagInterstitialIframeJavascript" PrefixI False) U1) (C1 (MetaCons "PTFIPlacementTagInterstitialIframeJavascriptLegacy" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "PTFIPlacementTagInterstitialInternalRedirect" PrefixI False) U1) (C1 (MetaCons "PTFIPlacementTagInterstitialJavascript" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PTFIPlacementTagInterstitialJavascriptLegacy" PrefixI False) U1) (C1 (MetaCons "PTFIPlacementTagJavascript" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PTFIPlacementTagJavascriptLegacy" PrefixI False) U1) (C1 (MetaCons "PTFIPlacementTagStandard" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PTFIPlacementTagTracking" PrefixI False) U1) ((:+:) (C1 (MetaCons "PTFIPlacementTagTrackingIframe" PrefixI False) U1) (C1 (MetaCons "PTFIPlacementTagTrackingJavascript" PrefixI False) U1))))))

Order

data Order Source #

Describes properties of a DoubleClick Planning order.

See: order smart constructor.

Instances

Eq Order Source # 

Methods

(==) :: Order -> Order -> Bool #

(/=) :: Order -> Order -> Bool #

Data Order Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Order -> c Order #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Order #

toConstr :: Order -> Constr #

dataTypeOf :: Order -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Order) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Order) #

gmapT :: (forall b. Data b => b -> b) -> Order -> Order #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Order -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Order -> r #

gmapQ :: (forall d. Data d => d -> u) -> Order -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Order -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Order -> m Order #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Order -> m Order #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Order -> m Order #

Show Order Source # 

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

Generic Order Source # 

Associated Types

type Rep Order :: * -> * #

Methods

from :: Order -> Rep Order x #

to :: Rep Order x -> Order #

ToJSON Order Source # 
FromJSON Order Source # 
type Rep Order Source # 
type Rep Order = D1 (MetaData "Order" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Order'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_oSellerOrderId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_oSellerOrganizationName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_oKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_oAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_oPlanningTermId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_oAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_oName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_oSiteNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) ((:*:) (S1 (MetaSel (Just Symbol "_oLastModifiedInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo))) (S1 (MetaSel (Just Symbol "_oBuyerOrganizationName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_oId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_oBuyerInvoiceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_oComments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_oProjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_oSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_oNotes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_oContacts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [OrderContact])))) ((:*:) (S1 (MetaSel (Just Symbol "_oSiteId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64]))) ((:*:) (S1 (MetaSel (Just Symbol "_oTermsAndConditions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_oApproverUserProFileIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64])))))))))

oSellerOrderId :: Lens' Order (Maybe Text) Source #

Seller order ID associated with this order.

oSellerOrganizationName :: Lens' Order (Maybe Text) Source #

Name of the seller organization.

oKind :: Lens' Order Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#order".

oAdvertiserId :: Lens' Order (Maybe Int64) Source #

Advertiser ID of this order.

oPlanningTermId :: Lens' Order (Maybe Int64) Source #

ID of the terms and conditions template used in this order.

oAccountId :: Lens' Order (Maybe Int64) Source #

Account ID of this order.

oName :: Lens' Order (Maybe Text) Source #

Name of this order.

oSiteNames :: Lens' Order [Text] Source #

Free-form site names this order is associated with.

oLastModifiedInfo :: Lens' Order (Maybe LastModifiedInfo) Source #

Information about the most recent modification of this order.

oBuyerOrganizationName :: Lens' Order (Maybe Text) Source #

Name of the buyer organization.

oId :: Lens' Order (Maybe Int64) Source #

ID of this order. This is a read-only, auto-generated field.

oBuyerInvoiceId :: Lens' Order (Maybe Text) Source #

Buyer invoice ID associated with this order.

oComments :: Lens' Order (Maybe Text) Source #

Comments in this order.

oProjectId :: Lens' Order (Maybe Int64) Source #

Project ID of this order.

oSubAccountId :: Lens' Order (Maybe Int64) Source #

Subaccount ID of this order.

oNotes :: Lens' Order (Maybe Text) Source #

Notes of this order.

oContacts :: Lens' Order [OrderContact] Source #

Contacts for this order.

oSiteId :: Lens' Order [Int64] Source #

Site IDs this order is associated with.

oTermsAndConditions :: Lens' Order (Maybe Text) Source #

Terms and conditions of this order.

oApproverUserProFileIds :: Lens' Order [Int64] Source #

IDs for users that have to approve documents created for this order.

CreativeAssetId

data CreativeAssetId Source #

Creative Asset ID.

See: creativeAssetId smart constructor.

Instances

Eq CreativeAssetId Source # 
Data CreativeAssetId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetId -> c CreativeAssetId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetId #

toConstr :: CreativeAssetId -> Constr #

dataTypeOf :: CreativeAssetId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetId) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetId -> CreativeAssetId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetId -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetId -> m CreativeAssetId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetId -> m CreativeAssetId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetId -> m CreativeAssetId #

Show CreativeAssetId Source # 
Generic CreativeAssetId Source # 
ToJSON CreativeAssetId Source # 
FromJSON CreativeAssetId Source # 
type Rep CreativeAssetId Source # 
type Rep CreativeAssetId = D1 (MetaData "CreativeAssetId" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeAssetId'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_caiName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_caiType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetIdType)))))

creativeAssetId :: CreativeAssetId Source #

Creates a value of CreativeAssetId with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

caiName :: Lens' CreativeAssetId (Maybe Text) Source #

Name of the creative asset. This is a required field while inserting an asset. After insertion, this assetIdentifier is used to identify the uploaded asset. Characters in the name must be alphanumeric or one of the following: ".-_ ". Spaces are allowed.

caiType :: Lens' CreativeAssetId (Maybe CreativeAssetIdType) Source #

Type of asset to upload. This is a required field. IMAGE is solely used for IMAGE creatives. Other image assets should use HTML_IMAGE.

FrequencyCap

data FrequencyCap Source #

Frequency Cap.

See: frequencyCap smart constructor.

Instances

Eq FrequencyCap Source # 
Data FrequencyCap Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FrequencyCap -> c FrequencyCap #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FrequencyCap #

toConstr :: FrequencyCap -> Constr #

dataTypeOf :: FrequencyCap -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FrequencyCap) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FrequencyCap) #

gmapT :: (forall b. Data b => b -> b) -> FrequencyCap -> FrequencyCap #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FrequencyCap -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FrequencyCap -> r #

gmapQ :: (forall d. Data d => d -> u) -> FrequencyCap -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FrequencyCap -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FrequencyCap -> m FrequencyCap #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FrequencyCap -> m FrequencyCap #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FrequencyCap -> m FrequencyCap #

Show FrequencyCap Source # 
Generic FrequencyCap Source # 

Associated Types

type Rep FrequencyCap :: * -> * #

ToJSON FrequencyCap Source # 
FromJSON FrequencyCap Source # 
type Rep FrequencyCap Source # 
type Rep FrequencyCap = D1 (MetaData "FrequencyCap" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FrequencyCap'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fcImpressions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_fcDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))

frequencyCap :: FrequencyCap Source #

Creates a value of FrequencyCap with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

fcImpressions :: Lens' FrequencyCap (Maybe Int64) Source #

Number of times an individual user can be served the ad within the specified duration. The maximum allowed is 15.

fcDuration :: Lens' FrequencyCap (Maybe Int64) Source #

Duration of time, in seconds, for this frequency cap. The maximum duration is 90 days in seconds, or 7,776,000.

File

data File Source #

Represents a File resource. A file contains the metadata for a report run. It shows the status of the run and holds the URLs to the generated report data if the run is finished and the status is "REPORT_AVAILABLE".

See: file smart constructor.

Instances

Eq File Source # 

Methods

(==) :: File -> File -> Bool #

(/=) :: File -> File -> Bool #

Data File Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> File -> c File #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c File #

toConstr :: File -> Constr #

dataTypeOf :: File -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c File) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c File) #

gmapT :: (forall b. Data b => b -> b) -> File -> File #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> File -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> File -> r #

gmapQ :: (forall d. Data d => d -> u) -> File -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> File -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> File -> m File #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> File -> m File #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> File -> m File #

Show File Source # 

Methods

showsPrec :: Int -> File -> ShowS #

show :: File -> String #

showList :: [File] -> ShowS #

Generic File Source # 

Associated Types

type Rep File :: * -> * #

Methods

from :: File -> Rep File x #

to :: Rep File x -> File #

ToJSON File Source # 
FromJSON File Source # 
type Rep File Source # 

file :: File Source #

Creates a value of File with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

filStatus :: Lens' File (Maybe FileStatus) Source #

The status of the report file.

filEtag :: Lens' File (Maybe Text) Source #

The eTag of this response for caching purposes.

filKind :: Lens' File Text Source #

The kind of resource this is, in this case dfareporting#file.

filURLs :: Lens' File (Maybe FileURLs) Source #

The URLs where the completed report file can be downloaded.

filReportId :: Lens' File (Maybe Int64) Source #

The ID of the report this file was generated from.

filDateRange :: Lens' File (Maybe DateRange) Source #

The date range for which the file has report data. The date range will always be the absolute date range for which the report is run.

filFormat :: Lens' File (Maybe FileFormat) Source #

The output format of the report. Only available once the file is available.

filLastModifiedTime :: Lens' File (Maybe Int64) Source #

The timestamp in milliseconds since epoch when this file was last modified.

filId :: Lens' File (Maybe Int64) Source #

The unique ID of this report file.

filFileName :: Lens' File (Maybe Text) Source #

The filename of the file.

CreativeSettings

data CreativeSettings Source #

Creative Settings

See: creativeSettings smart constructor.

Instances

Eq CreativeSettings Source # 
Data CreativeSettings Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeSettings -> c CreativeSettings #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeSettings #

toConstr :: CreativeSettings -> Constr #

dataTypeOf :: CreativeSettings -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeSettings) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeSettings) #

gmapT :: (forall b. Data b => b -> b) -> CreativeSettings -> CreativeSettings #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeSettings -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeSettings -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeSettings -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeSettings -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeSettings -> m CreativeSettings #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeSettings -> m CreativeSettings #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeSettings -> m CreativeSettings #

Show CreativeSettings Source # 
Generic CreativeSettings Source # 
ToJSON CreativeSettings Source # 
FromJSON CreativeSettings Source # 
type Rep CreativeSettings Source # 
type Rep CreativeSettings = D1 (MetaData "CreativeSettings" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeSettings'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_csIFrameHeader") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_csIFrameFooter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

creativeSettings :: CreativeSettings Source #

Creates a value of CreativeSettings with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

csIFrameHeader :: Lens' CreativeSettings (Maybe Text) Source #

Header text for iFrames for this site. Must be less than or equal to 2000 characters long.

csIFrameFooter :: Lens' CreativeSettings (Maybe Text) Source #

Header text for iFrames for this site. Must be less than or equal to 2000 characters long.

DynamicTargetingKeyObjectType

data DynamicTargetingKeyObjectType Source #

Type of the object of this dynamic targeting key. This is a required field.

Constructors

DTKOTObjectAd
OBJECT_AD
DTKOTObjectAdvertiser
OBJECT_ADVERTISER
DTKOTObjectCreative
OBJECT_CREATIVE
DTKOTObjectPlacement
OBJECT_PLACEMENT

Instances

Enum DynamicTargetingKeyObjectType Source # 
Eq DynamicTargetingKeyObjectType Source # 
Data DynamicTargetingKeyObjectType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DynamicTargetingKeyObjectType -> c DynamicTargetingKeyObjectType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DynamicTargetingKeyObjectType #

toConstr :: DynamicTargetingKeyObjectType -> Constr #

dataTypeOf :: DynamicTargetingKeyObjectType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DynamicTargetingKeyObjectType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DynamicTargetingKeyObjectType) #

gmapT :: (forall b. Data b => b -> b) -> DynamicTargetingKeyObjectType -> DynamicTargetingKeyObjectType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DynamicTargetingKeyObjectType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DynamicTargetingKeyObjectType -> r #

gmapQ :: (forall d. Data d => d -> u) -> DynamicTargetingKeyObjectType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DynamicTargetingKeyObjectType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DynamicTargetingKeyObjectType -> m DynamicTargetingKeyObjectType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DynamicTargetingKeyObjectType -> m DynamicTargetingKeyObjectType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DynamicTargetingKeyObjectType -> m DynamicTargetingKeyObjectType #

Ord DynamicTargetingKeyObjectType Source # 
Read DynamicTargetingKeyObjectType Source # 
Show DynamicTargetingKeyObjectType Source # 
Generic DynamicTargetingKeyObjectType Source # 
Hashable DynamicTargetingKeyObjectType Source # 
ToJSON DynamicTargetingKeyObjectType Source # 
FromJSON DynamicTargetingKeyObjectType Source # 
FromHttpApiData DynamicTargetingKeyObjectType Source # 
ToHttpApiData DynamicTargetingKeyObjectType Source # 
type Rep DynamicTargetingKeyObjectType Source # 
type Rep DynamicTargetingKeyObjectType = D1 (MetaData "DynamicTargetingKeyObjectType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "DTKOTObjectAd" PrefixI False) U1) (C1 (MetaCons "DTKOTObjectAdvertiser" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DTKOTObjectCreative" PrefixI False) U1) (C1 (MetaCons "DTKOTObjectPlacement" PrefixI False) U1)))

ReportType

data ReportType Source #

The type of the report.

Constructors

RTCrossDimensionReach
CROSS_DIMENSION_REACH
RTFloodlight
FLOODLIGHT
RTPathToConversion
PATH_TO_CONVERSION
RTReach
REACH
RTStandard
STANDARD

Instances

Enum ReportType Source # 
Eq ReportType Source # 
Data ReportType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportType -> c ReportType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportType #

toConstr :: ReportType -> Constr #

dataTypeOf :: ReportType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReportType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportType) #

gmapT :: (forall b. Data b => b -> b) -> ReportType -> ReportType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportType -> m ReportType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportType -> m ReportType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportType -> m ReportType #

Ord ReportType Source # 
Read ReportType Source # 
Show ReportType Source # 
Generic ReportType Source # 

Associated Types

type Rep ReportType :: * -> * #

Hashable ReportType Source # 
ToJSON ReportType Source # 
FromJSON ReportType Source # 
FromHttpApiData ReportType Source # 
ToHttpApiData ReportType Source # 
type Rep ReportType Source # 
type Rep ReportType = D1 (MetaData "ReportType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "RTCrossDimensionReach" PrefixI False) U1) (C1 (MetaCons "RTFloodlight" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RTPathToConversion" PrefixI False) U1) ((:+:) (C1 (MetaCons "RTReach" PrefixI False) U1) (C1 (MetaCons "RTStandard" PrefixI False) U1))))

CreativeAssetMetadataWarnedValidationRulesItem

data CreativeAssetMetadataWarnedValidationRulesItem Source #

Constructors

ADMobReferenced
ADMOB_REFERENCED
AssetFormatUnsupportedDcm
ASSET_FORMAT_UNSUPPORTED_DCM
AssetInvalid
ASSET_INVALID
ClickTagHardCoded
CLICK_TAG_HARD_CODED
ClickTagInvalid
CLICK_TAG_INVALID
ClickTagInGwd
CLICK_TAG_IN_GWD
ClickTagMissing
CLICK_TAG_MISSING
ClickTagMoreThanOne
CLICK_TAG_MORE_THAN_ONE
ClickTagNonTopLevel
CLICK_TAG_NON_TOP_LEVEL
ComponentUnsupportedDcm
COMPONENT_UNSUPPORTED_DCM
EnablerUnsupportedMethodDcm
ENABLER_UNSUPPORTED_METHOD_DCM
ExternalFileReferenced
EXTERNAL_FILE_REFERENCED
FileDetailEmpty
FILE_DETAIL_EMPTY
FileTypeInvalid
FILE_TYPE_INVALID
GwdPropertiesInvalid
GWD_PROPERTIES_INVALID
HTML5FeatureUnsupported
HTML5_FEATURE_UNSUPPORTED
LinkedFileNotFound
LINKED_FILE_NOT_FOUND
MaxFlashVersion11
MAX_FLASH_VERSION_11
MraidReferenced
MRAID_REFERENCED
NotSSLCompliant
NOT_SSL_COMPLIANT
OrphanedAsset
ORPHANED_ASSET
PrimaryHTMLMissing
PRIMARY_HTML_MISSING
SvgInvalid
SVG_INVALID
ZipInvalid
ZIP_INVALID

Instances

Enum CreativeAssetMetadataWarnedValidationRulesItem Source # 
Eq CreativeAssetMetadataWarnedValidationRulesItem Source # 
Data CreativeAssetMetadataWarnedValidationRulesItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetMetadataWarnedValidationRulesItem -> c CreativeAssetMetadataWarnedValidationRulesItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetMetadataWarnedValidationRulesItem #

toConstr :: CreativeAssetMetadataWarnedValidationRulesItem -> Constr #

dataTypeOf :: CreativeAssetMetadataWarnedValidationRulesItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetMetadataWarnedValidationRulesItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetMetadataWarnedValidationRulesItem) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetMetadataWarnedValidationRulesItem -> CreativeAssetMetadataWarnedValidationRulesItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetMetadataWarnedValidationRulesItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetMetadataWarnedValidationRulesItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetMetadataWarnedValidationRulesItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetMetadataWarnedValidationRulesItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetMetadataWarnedValidationRulesItem -> m CreativeAssetMetadataWarnedValidationRulesItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetMetadataWarnedValidationRulesItem -> m CreativeAssetMetadataWarnedValidationRulesItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetMetadataWarnedValidationRulesItem -> m CreativeAssetMetadataWarnedValidationRulesItem #

Ord CreativeAssetMetadataWarnedValidationRulesItem Source # 
Read CreativeAssetMetadataWarnedValidationRulesItem Source # 
Show CreativeAssetMetadataWarnedValidationRulesItem Source # 
Generic CreativeAssetMetadataWarnedValidationRulesItem Source # 
Hashable CreativeAssetMetadataWarnedValidationRulesItem Source # 
ToJSON CreativeAssetMetadataWarnedValidationRulesItem Source # 
FromJSON CreativeAssetMetadataWarnedValidationRulesItem Source # 
FromHttpApiData CreativeAssetMetadataWarnedValidationRulesItem Source # 
ToHttpApiData CreativeAssetMetadataWarnedValidationRulesItem Source # 
type Rep CreativeAssetMetadataWarnedValidationRulesItem Source # 
type Rep CreativeAssetMetadataWarnedValidationRulesItem = D1 (MetaData "CreativeAssetMetadataWarnedValidationRulesItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ADMobReferenced" PrefixI False) U1) ((:+:) (C1 (MetaCons "AssetFormatUnsupportedDcm" PrefixI False) U1) (C1 (MetaCons "AssetInvalid" PrefixI False) U1))) ((:+:) (C1 (MetaCons "ClickTagHardCoded" PrefixI False) U1) ((:+:) (C1 (MetaCons "ClickTagInvalid" PrefixI False) U1) (C1 (MetaCons "ClickTagInGwd" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "ClickTagMissing" PrefixI False) U1) ((:+:) (C1 (MetaCons "ClickTagMoreThanOne" PrefixI False) U1) (C1 (MetaCons "ClickTagNonTopLevel" PrefixI False) U1))) ((:+:) (C1 (MetaCons "ComponentUnsupportedDcm" PrefixI False) U1) ((:+:) (C1 (MetaCons "EnablerUnsupportedMethodDcm" PrefixI False) U1) (C1 (MetaCons "ExternalFileReferenced" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "FileDetailEmpty" PrefixI False) U1) ((:+:) (C1 (MetaCons "FileTypeInvalid" PrefixI False) U1) (C1 (MetaCons "GwdPropertiesInvalid" PrefixI False) U1))) ((:+:) (C1 (MetaCons "HTML5FeatureUnsupported" PrefixI False) U1) ((:+:) (C1 (MetaCons "LinkedFileNotFound" PrefixI False) U1) (C1 (MetaCons "MaxFlashVersion11" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "MraidReferenced" PrefixI False) U1) ((:+:) (C1 (MetaCons "NotSSLCompliant" PrefixI False) U1) (C1 (MetaCons "OrphanedAsset" PrefixI False) U1))) ((:+:) (C1 (MetaCons "PrimaryHTMLMissing" PrefixI False) U1) ((:+:) (C1 (MetaCons "SvgInvalid" PrefixI False) U1) (C1 (MetaCons "ZipInvalid" PrefixI False) U1))))))

CreativeGroupsListResponse

data CreativeGroupsListResponse Source #

Creative Group List Response

See: creativeGroupsListResponse smart constructor.

Instances

Eq CreativeGroupsListResponse Source # 
Data CreativeGroupsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeGroupsListResponse -> c CreativeGroupsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeGroupsListResponse #

toConstr :: CreativeGroupsListResponse -> Constr #

dataTypeOf :: CreativeGroupsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeGroupsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeGroupsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> CreativeGroupsListResponse -> CreativeGroupsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeGroupsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeGroupsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeGroupsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeGroupsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeGroupsListResponse -> m CreativeGroupsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeGroupsListResponse -> m CreativeGroupsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeGroupsListResponse -> m CreativeGroupsListResponse #

Show CreativeGroupsListResponse Source # 
Generic CreativeGroupsListResponse Source # 
ToJSON CreativeGroupsListResponse Source # 
FromJSON CreativeGroupsListResponse Source # 
type Rep CreativeGroupsListResponse Source # 
type Rep CreativeGroupsListResponse = D1 (MetaData "CreativeGroupsListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeGroupsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cglrCreativeGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeGroup]))) ((:*:) (S1 (MetaSel (Just Symbol "_cglrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cglrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

creativeGroupsListResponse :: CreativeGroupsListResponse Source #

Creates a value of CreativeGroupsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cglrNextPageToken :: Lens' CreativeGroupsListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

cglrKind :: Lens' CreativeGroupsListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#creativeGroupsListResponse".

AdSlotPaymentSourceType

data AdSlotPaymentSourceType Source #

Payment source type of this ad slot.

Constructors

PlanningPaymentSourceTypeAgencyPaid
PLANNING_PAYMENT_SOURCE_TYPE_AGENCY_PAID
PlanningPaymentSourceTypePublisherPaid
PLANNING_PAYMENT_SOURCE_TYPE_PUBLISHER_PAID

Instances

Enum AdSlotPaymentSourceType Source # 
Eq AdSlotPaymentSourceType Source # 
Data AdSlotPaymentSourceType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdSlotPaymentSourceType -> c AdSlotPaymentSourceType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdSlotPaymentSourceType #

toConstr :: AdSlotPaymentSourceType -> Constr #

dataTypeOf :: AdSlotPaymentSourceType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdSlotPaymentSourceType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdSlotPaymentSourceType) #

gmapT :: (forall b. Data b => b -> b) -> AdSlotPaymentSourceType -> AdSlotPaymentSourceType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdSlotPaymentSourceType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdSlotPaymentSourceType -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdSlotPaymentSourceType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdSlotPaymentSourceType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdSlotPaymentSourceType -> m AdSlotPaymentSourceType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdSlotPaymentSourceType -> m AdSlotPaymentSourceType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdSlotPaymentSourceType -> m AdSlotPaymentSourceType #

Ord AdSlotPaymentSourceType Source # 
Read AdSlotPaymentSourceType Source # 
Show AdSlotPaymentSourceType Source # 
Generic AdSlotPaymentSourceType Source # 
Hashable AdSlotPaymentSourceType Source # 
ToJSON AdSlotPaymentSourceType Source # 
FromJSON AdSlotPaymentSourceType Source # 
FromHttpApiData AdSlotPaymentSourceType Source # 
ToHttpApiData AdSlotPaymentSourceType Source # 
type Rep AdSlotPaymentSourceType Source # 
type Rep AdSlotPaymentSourceType = D1 (MetaData "AdSlotPaymentSourceType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PlanningPaymentSourceTypeAgencyPaid" PrefixI False) U1) (C1 (MetaCons "PlanningPaymentSourceTypePublisherPaid" PrefixI False) U1))

MobileCarriersListResponse

data MobileCarriersListResponse Source #

Mobile Carrier List Response

See: mobileCarriersListResponse smart constructor.

Instances

Eq MobileCarriersListResponse Source # 
Data MobileCarriersListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MobileCarriersListResponse -> c MobileCarriersListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MobileCarriersListResponse #

toConstr :: MobileCarriersListResponse -> Constr #

dataTypeOf :: MobileCarriersListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MobileCarriersListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MobileCarriersListResponse) #

gmapT :: (forall b. Data b => b -> b) -> MobileCarriersListResponse -> MobileCarriersListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MobileCarriersListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MobileCarriersListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> MobileCarriersListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MobileCarriersListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MobileCarriersListResponse -> m MobileCarriersListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MobileCarriersListResponse -> m MobileCarriersListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MobileCarriersListResponse -> m MobileCarriersListResponse #

Show MobileCarriersListResponse Source # 
Generic MobileCarriersListResponse Source # 
ToJSON MobileCarriersListResponse Source # 
FromJSON MobileCarriersListResponse Source # 
type Rep MobileCarriersListResponse Source # 
type Rep MobileCarriersListResponse = D1 (MetaData "MobileCarriersListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "MobileCarriersListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_mclrMobileCarriers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [MobileCarrier]))) (S1 (MetaSel (Just Symbol "_mclrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

mobileCarriersListResponse :: MobileCarriersListResponse Source #

Creates a value of MobileCarriersListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

mclrKind :: Lens' MobileCarriersListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#mobileCarriersListResponse".

LandingPagesListResponse

data LandingPagesListResponse Source #

Landing Page List Response

See: landingPagesListResponse smart constructor.

Instances

Eq LandingPagesListResponse Source # 
Data LandingPagesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LandingPagesListResponse -> c LandingPagesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LandingPagesListResponse #

toConstr :: LandingPagesListResponse -> Constr #

dataTypeOf :: LandingPagesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LandingPagesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LandingPagesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> LandingPagesListResponse -> LandingPagesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LandingPagesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LandingPagesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> LandingPagesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LandingPagesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LandingPagesListResponse -> m LandingPagesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LandingPagesListResponse -> m LandingPagesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LandingPagesListResponse -> m LandingPagesListResponse #

Show LandingPagesListResponse Source # 
Generic LandingPagesListResponse Source # 
ToJSON LandingPagesListResponse Source # 
FromJSON LandingPagesListResponse Source # 
type Rep LandingPagesListResponse Source # 
type Rep LandingPagesListResponse = D1 (MetaData "LandingPagesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "LandingPagesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_lplrLandingPages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [LandingPage]))) (S1 (MetaSel (Just Symbol "_lplrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

landingPagesListResponse :: LandingPagesListResponse Source #

Creates a value of LandingPagesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lplrKind :: Lens' LandingPagesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#landingPagesListResponse".

AccountPermissionAccountProFilesItem

data AccountPermissionAccountProFilesItem Source #

Constructors

APAPFIAccountProFileBasic
ACCOUNT_PROFILE_BASIC
APAPFIAccountProFileStandard
ACCOUNT_PROFILE_STANDARD

Instances

Enum AccountPermissionAccountProFilesItem Source # 
Eq AccountPermissionAccountProFilesItem Source # 
Data AccountPermissionAccountProFilesItem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountPermissionAccountProFilesItem -> c AccountPermissionAccountProFilesItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountPermissionAccountProFilesItem #

toConstr :: AccountPermissionAccountProFilesItem -> Constr #

dataTypeOf :: AccountPermissionAccountProFilesItem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountPermissionAccountProFilesItem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountPermissionAccountProFilesItem) #

gmapT :: (forall b. Data b => b -> b) -> AccountPermissionAccountProFilesItem -> AccountPermissionAccountProFilesItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountPermissionAccountProFilesItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountPermissionAccountProFilesItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountPermissionAccountProFilesItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountPermissionAccountProFilesItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountPermissionAccountProFilesItem -> m AccountPermissionAccountProFilesItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountPermissionAccountProFilesItem -> m AccountPermissionAccountProFilesItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountPermissionAccountProFilesItem -> m AccountPermissionAccountProFilesItem #

Ord AccountPermissionAccountProFilesItem Source # 
Read AccountPermissionAccountProFilesItem Source # 
Show AccountPermissionAccountProFilesItem Source # 
Generic AccountPermissionAccountProFilesItem Source # 
Hashable AccountPermissionAccountProFilesItem Source # 
ToJSON AccountPermissionAccountProFilesItem Source # 
FromJSON AccountPermissionAccountProFilesItem Source # 
FromHttpApiData AccountPermissionAccountProFilesItem Source # 
ToHttpApiData AccountPermissionAccountProFilesItem Source # 
type Rep AccountPermissionAccountProFilesItem Source # 
type Rep AccountPermissionAccountProFilesItem = D1 (MetaData "AccountPermissionAccountProFilesItem" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "APAPFIAccountProFileBasic" PrefixI False) U1) (C1 (MetaCons "APAPFIAccountProFileStandard" PrefixI False) U1))

CreativeAssetMetadata

data CreativeAssetMetadata Source #

CreativeAssets contains properties of a creative asset file which will be uploaded or has already been uploaded. Refer to the creative sample code for how to upload assets and insert a creative.

See: creativeAssetMetadata smart constructor.

Instances

Eq CreativeAssetMetadata Source # 
Data CreativeAssetMetadata Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetMetadata -> c CreativeAssetMetadata #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetMetadata #

toConstr :: CreativeAssetMetadata -> Constr #

dataTypeOf :: CreativeAssetMetadata -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetMetadata) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetMetadata) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetMetadata -> CreativeAssetMetadata #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetMetadata -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetMetadata -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetMetadata -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetMetadata -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetMetadata -> m CreativeAssetMetadata #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetMetadata -> m CreativeAssetMetadata #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetMetadata -> m CreativeAssetMetadata #

Show CreativeAssetMetadata Source # 
Generic CreativeAssetMetadata Source # 
ToJSON CreativeAssetMetadata Source # 
FromJSON CreativeAssetMetadata Source # 
type Rep CreativeAssetMetadata Source # 
type Rep CreativeAssetMetadata = D1 (MetaData "CreativeAssetMetadata" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "CreativeAssetMetadata'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_camaKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_camaAssetIdentifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CreativeAssetId)))) ((:*:) (S1 (MetaSel (Just Symbol "_camaClickTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ClickTag]))) ((:*:) (S1 (MetaSel (Just Symbol "_camaWarnedValidationRules") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeAssetMetadataWarnedValidationRulesItem]))) (S1 (MetaSel (Just Symbol "_camaDetectedFeatures") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [CreativeAssetMetadataDetectedFeaturesItem])))))))

creativeAssetMetadata :: CreativeAssetMetadata Source #

Creates a value of CreativeAssetMetadata with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

camaKind :: Lens' CreativeAssetMetadata Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#creativeAssetMetadata".

camaAssetIdentifier :: Lens' CreativeAssetMetadata (Maybe CreativeAssetId) Source #

ID of the creative asset. This is a required field.

camaClickTags :: Lens' CreativeAssetMetadata [ClickTag] Source #

List of detected click tags for assets. This is a read-only auto-generated field.

camaWarnedValidationRules :: Lens' CreativeAssetMetadata [CreativeAssetMetadataWarnedValidationRulesItem] Source #

Rules validated during code generation that generated a warning. This is a read-only, auto-generated field. Possible values are: - "ADMOB_REFERENCED" - "ASSET_FORMAT_UNSUPPORTED_DCM" - "ASSET_INVALID" - "CLICK_TAG_HARD_CODED" - "CLICK_TAG_INVALID" - "CLICK_TAG_IN_GWD" - "CLICK_TAG_MISSING" - "CLICK_TAG_MORE_THAN_ONE" - "CLICK_TAG_NON_TOP_LEVEL" - "COMPONENT_UNSUPPORTED_DCM" - "ENABLER_UNSUPPORTED_METHOD_DCM" - "EXTERNAL_FILE_REFERENCED" - "FILE_DETAIL_EMPTY" - "FILE_TYPE_INVALID" - "GWD_PROPERTIES_INVALID" - "HTML5_FEATURE_UNSUPPORTED" - "LINKED_FILE_NOT_FOUND" - "MAX_FLASH_VERSION_11" - "MRAID_REFERENCED" - "NOT_SSL_COMPLIANT" - "ORPHANED_ASSET" - "PRIMARY_HTML_MISSING" - "SVG_INVALID" - "ZIP_INVALID"

camaDetectedFeatures :: Lens' CreativeAssetMetadata [CreativeAssetMetadataDetectedFeaturesItem] Source #

List of feature dependencies for the creative asset that are detected by DCM. Feature dependencies are features that a browser must be able to support in order to render your HTML5 creative correctly. This is a read-only, auto-generated field.

OmnitureSettings

data OmnitureSettings Source #

Omniture Integration Settings.

See: omnitureSettings smart constructor.

Instances

Eq OmnitureSettings Source # 
Data OmnitureSettings Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OmnitureSettings -> c OmnitureSettings #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OmnitureSettings #

toConstr :: OmnitureSettings -> Constr #

dataTypeOf :: OmnitureSettings -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OmnitureSettings) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OmnitureSettings) #

gmapT :: (forall b. Data b => b -> b) -> OmnitureSettings -> OmnitureSettings #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OmnitureSettings -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OmnitureSettings -> r #

gmapQ :: (forall d. Data d => d -> u) -> OmnitureSettings -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OmnitureSettings -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OmnitureSettings -> m OmnitureSettings #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OmnitureSettings -> m OmnitureSettings #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OmnitureSettings -> m OmnitureSettings #

Show OmnitureSettings Source # 
Generic OmnitureSettings Source # 
ToJSON OmnitureSettings Source # 
FromJSON OmnitureSettings Source # 
type Rep OmnitureSettings Source # 
type Rep OmnitureSettings = D1 (MetaData "OmnitureSettings" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "OmnitureSettings'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_osOmnitureCostDataEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_osOmnitureIntegrationEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))

omnitureSettings :: OmnitureSettings Source #

Creates a value of OmnitureSettings with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

osOmnitureCostDataEnabled :: Lens' OmnitureSettings (Maybe Bool) Source #

Whether placement cost data will be sent to Omniture. This property can be enabled only if omnitureIntegrationEnabled is true.

osOmnitureIntegrationEnabled :: Lens' OmnitureSettings (Maybe Bool) Source #

Whether Omniture integration is enabled. This property can be enabled only when the "Advanced Ad Serving" account setting is enabled.

ConnectionType

data ConnectionType Source #

Contains information about an internet connection type that can be targeted by ads. Clients can use the connection type to target mobile vs. broadband users.

See: connectionType smart constructor.

Instances

Eq ConnectionType Source # 
Data ConnectionType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConnectionType -> c ConnectionType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConnectionType #

toConstr :: ConnectionType -> Constr #

dataTypeOf :: ConnectionType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConnectionType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConnectionType) #

gmapT :: (forall b. Data b => b -> b) -> ConnectionType -> ConnectionType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConnectionType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConnectionType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConnectionType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConnectionType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConnectionType -> m ConnectionType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConnectionType -> m ConnectionType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConnectionType -> m ConnectionType #

Show ConnectionType Source # 
Generic ConnectionType Source # 

Associated Types

type Rep ConnectionType :: * -> * #

ToJSON ConnectionType Source # 
FromJSON ConnectionType Source # 
type Rep ConnectionType Source # 
type Rep ConnectionType = D1 (MetaData "ConnectionType" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ConnectionType'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cttKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_cttName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cttId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

connectionType :: ConnectionType Source #

Creates a value of ConnectionType with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cttKind :: Lens' ConnectionType Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#connectionType".

cttName :: Lens' ConnectionType (Maybe Text) Source #

Name of this connection type.

cttId :: Lens' ConnectionType (Maybe Int64) Source #

ID of this connection type.

CreativeCustomEventAdvertiserCustomEventType

data CreativeCustomEventAdvertiserCustomEventType Source #

Type of the event. This is a read-only field.

Constructors

AdvertiserEventCounter
ADVERTISER_EVENT_COUNTER
AdvertiserEventExit
ADVERTISER_EVENT_EXIT
AdvertiserEventTimer
ADVERTISER_EVENT_TIMER

Instances

Enum CreativeCustomEventAdvertiserCustomEventType Source # 
Eq CreativeCustomEventAdvertiserCustomEventType Source # 
Data CreativeCustomEventAdvertiserCustomEventType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeCustomEventAdvertiserCustomEventType -> c CreativeCustomEventAdvertiserCustomEventType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeCustomEventAdvertiserCustomEventType #

toConstr :: CreativeCustomEventAdvertiserCustomEventType -> Constr #

dataTypeOf :: CreativeCustomEventAdvertiserCustomEventType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeCustomEventAdvertiserCustomEventType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeCustomEventAdvertiserCustomEventType) #

gmapT :: (forall b. Data b => b -> b) -> CreativeCustomEventAdvertiserCustomEventType -> CreativeCustomEventAdvertiserCustomEventType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeCustomEventAdvertiserCustomEventType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeCustomEventAdvertiserCustomEventType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeCustomEventAdvertiserCustomEventType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeCustomEventAdvertiserCustomEventType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeCustomEventAdvertiserCustomEventType -> m CreativeCustomEventAdvertiserCustomEventType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeCustomEventAdvertiserCustomEventType -> m CreativeCustomEventAdvertiserCustomEventType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeCustomEventAdvertiserCustomEventType -> m CreativeCustomEventAdvertiserCustomEventType #

Ord CreativeCustomEventAdvertiserCustomEventType Source # 
Read CreativeCustomEventAdvertiserCustomEventType Source # 
Show CreativeCustomEventAdvertiserCustomEventType Source # 
Generic CreativeCustomEventAdvertiserCustomEventType Source # 
Hashable CreativeCustomEventAdvertiserCustomEventType Source # 
ToJSON CreativeCustomEventAdvertiserCustomEventType Source # 
FromJSON CreativeCustomEventAdvertiserCustomEventType Source # 
FromHttpApiData CreativeCustomEventAdvertiserCustomEventType Source # 
ToHttpApiData CreativeCustomEventAdvertiserCustomEventType Source # 
type Rep CreativeCustomEventAdvertiserCustomEventType Source # 
type Rep CreativeCustomEventAdvertiserCustomEventType = D1 (MetaData "CreativeCustomEventAdvertiserCustomEventType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "AdvertiserEventCounter" PrefixI False) U1) ((:+:) (C1 (MetaCons "AdvertiserEventExit" PrefixI False) U1) (C1 (MetaCons "AdvertiserEventTimer" PrefixI False) U1)))

PlacementGroup

data PlacementGroup Source #

Contains properties of a package or roadblock.

See: placementGroup smart constructor.

Instances

Eq PlacementGroup Source # 
Data PlacementGroup Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlacementGroup -> c PlacementGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlacementGroup #

toConstr :: PlacementGroup -> Constr #

dataTypeOf :: PlacementGroup -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlacementGroup) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlacementGroup) #

gmapT :: (forall b. Data b => b -> b) -> PlacementGroup -> PlacementGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroup -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlacementGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlacementGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlacementGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlacementGroup -> m PlacementGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroup -> m PlacementGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlacementGroup -> m PlacementGroup #

Show PlacementGroup Source # 
Generic PlacementGroup Source # 

Associated Types

type Rep PlacementGroup :: * -> * #

ToJSON PlacementGroup Source # 
FromJSON PlacementGroup Source # 
type Rep PlacementGroup Source # 
type Rep PlacementGroup = D1 (MetaData "PlacementGroup" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "PlacementGroup'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_plalPlacementStrategyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_plalSiteIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_plalPricingSchedule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PricingSchedule))))) ((:*:) (S1 (MetaSel (Just Symbol "_plalKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_plalCampaignIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_plalAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_plalAdvertiserIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) ((:*:) (S1 (MetaSel (Just Symbol "_plalCampaignId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_plalIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_plalPlacementGroupType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PlacementGroupPlacementGroupType))) (S1 (MetaSel (Just Symbol "_plalContentCategoryId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_plalDirectorySiteIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_plalAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_plalName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_plalDirectorySiteId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_plalCreateInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo))))) ((:*:) (S1 (MetaSel (Just Symbol "_plalChildPlacementIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64]))) ((:*:) (S1 (MetaSel (Just Symbol "_plalLastModifiedInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo))) (S1 (MetaSel (Just Symbol "_plalId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_plalPrimaryPlacementId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_plalSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_plalExternalId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_plalComment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_plalPrimaryPlacementIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue)))) ((:*:) (S1 (MetaSel (Just Symbol "_plalSiteId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_plalArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))))))

plalPlacementStrategyId :: Lens' PlacementGroup (Maybe Int64) Source #

ID of the placement strategy assigned to this placement group.

plalSiteIdDimensionValue :: Lens' PlacementGroup (Maybe DimensionValue) Source #

Dimension value for the ID of the site. This is a read-only, auto-generated field.

plalPricingSchedule :: Lens' PlacementGroup (Maybe PricingSchedule) Source #

Pricing schedule of this placement group. This field is required on insertion.

plalKind :: Lens' PlacementGroup Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#placementGroup".

plalCampaignIdDimensionValue :: Lens' PlacementGroup (Maybe DimensionValue) Source #

Dimension value for the ID of the campaign. This is a read-only, auto-generated field.

plalAdvertiserId :: Lens' PlacementGroup (Maybe Int64) Source #

Advertiser ID of this placement group. This is a required field on insertion.

plalAdvertiserIdDimensionValue :: Lens' PlacementGroup (Maybe DimensionValue) Source #

Dimension value for the ID of the advertiser. This is a read-only, auto-generated field.

plalCampaignId :: Lens' PlacementGroup (Maybe Int64) Source #

Campaign ID of this placement group. This field is required on insertion.

plalIdDimensionValue :: Lens' PlacementGroup (Maybe DimensionValue) Source #

Dimension value for the ID of this placement group. This is a read-only, auto-generated field.

plalPlacementGroupType :: Lens' PlacementGroup (Maybe PlacementGroupPlacementGroupType) Source #

Type of this placement group. A package is a simple group of placements that acts as a single pricing point for a group of tags. A roadblock is a group of placements that not only acts as a single pricing point, but also assumes that all the tags in it will be served at the same time. A roadblock requires one of its assigned placements to be marked as primary for reporting. This field is required on insertion.

plalContentCategoryId :: Lens' PlacementGroup (Maybe Int64) Source #

ID of the content category assigned to this placement group.

plalDirectorySiteIdDimensionValue :: Lens' PlacementGroup (Maybe DimensionValue) Source #

Dimension value for the ID of the directory site. This is a read-only, auto-generated field.

plalAccountId :: Lens' PlacementGroup (Maybe Int64) Source #

Account ID of this placement group. This is a read-only field that can be left blank.

plalName :: Lens' PlacementGroup (Maybe Text) Source #

Name of this placement group. This is a required field and must be less than 256 characters long.

plalDirectorySiteId :: Lens' PlacementGroup (Maybe Int64) Source #

Directory site ID associated with this placement group. On insert, you must set either this field or the site_id field to specify the site associated with this placement group. This is a required field that is read-only after insertion.

plalCreateInfo :: Lens' PlacementGroup (Maybe LastModifiedInfo) Source #

Information about the creation of this placement group. This is a read-only field.

plalChildPlacementIds :: Lens' PlacementGroup [Int64] Source #

IDs of placements which are assigned to this placement group. This is a read-only, auto-generated field.

plalLastModifiedInfo :: Lens' PlacementGroup (Maybe LastModifiedInfo) Source #

Information about the most recent modification of this placement group. This is a read-only field.

plalId :: Lens' PlacementGroup (Maybe Int64) Source #

ID of this placement group. This is a read-only, auto-generated field.

plalPrimaryPlacementId :: Lens' PlacementGroup (Maybe Int64) Source #

ID of the primary placement, used to calculate the media cost of a roadblock (placement group). Modifying this field will automatically modify the primary field on all affected roadblock child placements.

plalSubAccountId :: Lens' PlacementGroup (Maybe Int64) Source #

Subaccount ID of this placement group. This is a read-only field that can be left blank.

plalExternalId :: Lens' PlacementGroup (Maybe Text) Source #

External ID for this placement.

plalComment :: Lens' PlacementGroup (Maybe Text) Source #

Comments for this placement group.

plalPrimaryPlacementIdDimensionValue :: Lens' PlacementGroup (Maybe DimensionValue) Source #

Dimension value for the ID of the primary placement. This is a read-only, auto-generated field.

plalSiteId :: Lens' PlacementGroup (Maybe Int64) Source #

Site ID associated with this placement group. On insert, you must set either this field or the directorySiteId field to specify the site associated with this placement group. This is a required field that is read-only after insertion.

plalArchived :: Lens' PlacementGroup (Maybe Bool) Source #

Whether this placement group is archived.

EventTag

data EventTag Source #

Contains properties of an event tag.

See: eventTag smart constructor.

Instances

Eq EventTag Source # 
Data EventTag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventTag -> c EventTag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventTag #

toConstr :: EventTag -> Constr #

dataTypeOf :: EventTag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EventTag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventTag) #

gmapT :: (forall b. Data b => b -> b) -> EventTag -> EventTag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventTag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventTag -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventTag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventTag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventTag -> m EventTag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTag -> m EventTag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTag -> m EventTag #

Show EventTag Source # 
Generic EventTag Source # 

Associated Types

type Rep EventTag :: * -> * #

Methods

from :: EventTag -> Rep EventTag x #

to :: Rep EventTag x -> EventTag #

ToJSON EventTag Source # 
FromJSON EventTag Source # 
type Rep EventTag Source # 
type Rep EventTag = D1 (MetaData "EventTag" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "EventTag'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_etStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EventTagStatus))) (S1 (MetaSel (Just Symbol "_etExcludeFromAdxRequests") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_etEnabledByDefault") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_etKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_etCampaignIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_etAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_etURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_etAdvertiserIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_etSSLCompliant") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_etCampaignId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_etAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_etName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_etURLEscapeLevels") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_etSiteIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64]))) (S1 (MetaSel (Just Symbol "_etId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_etSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_etType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EventTagType))) (S1 (MetaSel (Just Symbol "_etSiteFilterType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EventTagSiteFilterType)))))))))

etStatus :: Lens' EventTag (Maybe EventTagStatus) Source #

Status of this event tag. Must be ENABLED for this event tag to fire. This is a required field.

etExcludeFromAdxRequests :: Lens' EventTag (Maybe Bool) Source #

Whether to remove this event tag from ads that are trafficked through DoubleClick Bid Manager to Ad Exchange. This may be useful if the event tag uses a pixel that is unapproved for Ad Exchange bids on one or more networks, such as the Google Display Network.

etEnabledByDefault :: Lens' EventTag (Maybe Bool) Source #

Whether this event tag should be automatically enabled for all of the advertiser's campaigns and ads.

etKind :: Lens' EventTag Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#eventTag".

etCampaignIdDimensionValue :: Lens' EventTag (Maybe DimensionValue) Source #

Dimension value for the ID of the campaign. This is a read-only, auto-generated field.

etAdvertiserId :: Lens' EventTag (Maybe Int64) Source #

Advertiser ID of this event tag. This field or the campaignId field is required on insertion.

etURL :: Lens' EventTag (Maybe Text) Source #

Payload URL for this event tag. The URL on a click-through event tag should have a landing page URL appended to the end of it. This field is required on insertion.

etAdvertiserIdDimensionValue :: Lens' EventTag (Maybe DimensionValue) Source #

Dimension value for the ID of the advertiser. This is a read-only, auto-generated field.

etSSLCompliant :: Lens' EventTag (Maybe Bool) Source #

Whether this tag is SSL-compliant or not. This is a read-only field.

etCampaignId :: Lens' EventTag (Maybe Int64) Source #

Campaign ID of this event tag. This field or the advertiserId field is required on insertion.

etAccountId :: Lens' EventTag (Maybe Int64) Source #

Account ID of this event tag. This is a read-only field that can be left blank.

etName :: Lens' EventTag (Maybe Text) Source #

Name of this event tag. This is a required field and must be less than 256 characters long.

etURLEscapeLevels :: Lens' EventTag (Maybe Int32) Source #

Number of times the landing page URL should be URL-escaped before being appended to the click-through event tag URL. Only applies to click-through event tags as specified by the event tag type.

etSiteIds :: Lens' EventTag [Int64] Source #

Filter list of site IDs associated with this event tag. The siteFilterType determines whether this is a whitelist or blacklist filter.

etId :: Lens' EventTag (Maybe Int64) Source #

ID of this event tag. This is a read-only, auto-generated field.

etSubAccountId :: Lens' EventTag (Maybe Int64) Source #

Subaccount ID of this event tag. This is a read-only field that can be left blank.

etType :: Lens' EventTag (Maybe EventTagType) Source #

Event tag type. Can be used to specify whether to use a third-party pixel, a third-party JavaScript URL, or a third-party click-through URL for either impression or click tracking. This is a required field.

etSiteFilterType :: Lens' EventTag (Maybe EventTagSiteFilterType) Source #

Site filter type for this event tag. If no type is specified then the event tag will be applied to all sites.

UserRolePermission

data UserRolePermission Source #

Contains properties of a user role permission.

See: userRolePermission smart constructor.

Instances

Eq UserRolePermission Source # 
Data UserRolePermission Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserRolePermission -> c UserRolePermission #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserRolePermission #

toConstr :: UserRolePermission -> Constr #

dataTypeOf :: UserRolePermission -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserRolePermission) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserRolePermission) #

gmapT :: (forall b. Data b => b -> b) -> UserRolePermission -> UserRolePermission #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserRolePermission -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserRolePermission -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserRolePermission -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserRolePermission -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserRolePermission -> m UserRolePermission #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRolePermission -> m UserRolePermission #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserRolePermission -> m UserRolePermission #

Show UserRolePermission Source # 
Generic UserRolePermission Source # 
ToJSON UserRolePermission Source # 
FromJSON UserRolePermission Source # 
type Rep UserRolePermission Source # 
type Rep UserRolePermission = D1 (MetaData "UserRolePermission" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "UserRolePermission'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_useKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_useAvailability") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UserRolePermissionAvailability)))) ((:*:) (S1 (MetaSel (Just Symbol "_useName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_useId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_usePermissionGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))))

userRolePermission :: UserRolePermission Source #

Creates a value of UserRolePermission with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

useKind :: Lens' UserRolePermission Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#userRolePermission".

useAvailability :: Lens' UserRolePermission (Maybe UserRolePermissionAvailability) Source #

Levels of availability for a user role permission.

useName :: Lens' UserRolePermission (Maybe Text) Source #

Name of this user role permission.

useId :: Lens' UserRolePermission (Maybe Int64) Source #

ID of this user role permission.

usePermissionGroupId :: Lens' UserRolePermission (Maybe Int64) Source #

ID of the permission group that this user role permission belongs to.

ChangeLogsListObjectType

data ChangeLogsListObjectType Source #

Select only change logs with the specified object type.

Constructors

CLLOTObjectAccount
OBJECT_ACCOUNT
CLLOTObjectAccountBillingFeature
OBJECT_ACCOUNT_BILLING_FEATURE
CLLOTObjectAd
OBJECT_AD
CLLOTObjectAdvertiser
OBJECT_ADVERTISER
CLLOTObjectAdvertiserGroup
OBJECT_ADVERTISER_GROUP
CLLOTObjectBillingAccountGroup
OBJECT_BILLING_ACCOUNT_GROUP
CLLOTObjectBillingFeature
OBJECT_BILLING_FEATURE
CLLOTObjectBillingMinimumFee
OBJECT_BILLING_MINIMUM_FEE
CLLOTObjectBillingProFile
OBJECT_BILLING_PROFILE
CLLOTObjectCampaign
OBJECT_CAMPAIGN
CLLOTObjectContentCategory
OBJECT_CONTENT_CATEGORY
CLLOTObjectCreative
OBJECT_CREATIVE
CLLOTObjectCreativeAsset
OBJECT_CREATIVE_ASSET
CLLOTObjectCreativeBundle
OBJECT_CREATIVE_BUNDLE
CLLOTObjectCreativeField
OBJECT_CREATIVE_FIELD
CLLOTObjectCreativeGroup
OBJECT_CREATIVE_GROUP
CLLOTObjectDfaSite
OBJECT_DFA_SITE
CLLOTObjectEventTag
OBJECT_EVENT_TAG
CLLOTObjectFloodlightActivityGroup
OBJECT_FLOODLIGHT_ACTIVITY_GROUP
CLLOTObjectFloodlightActvity
OBJECT_FLOODLIGHT_ACTVITY
CLLOTObjectFloodlightConfiguration
OBJECT_FLOODLIGHT_CONFIGURATION
CLLOTObjectInstreamCreative
OBJECT_INSTREAM_CREATIVE
CLLOTObjectLandingPage
OBJECT_LANDING_PAGE
CLLOTObjectMediaOrder
OBJECT_MEDIA_ORDER
CLLOTObjectPlacement
OBJECT_PLACEMENT
CLLOTObjectPlacementStrategy
OBJECT_PLACEMENT_STRATEGY
CLLOTObjectPlaystoreLink
OBJECT_PLAYSTORE_LINK
CLLOTObjectProvidedListClient
OBJECT_PROVIDED_LIST_CLIENT
CLLOTObjectRateCard
OBJECT_RATE_CARD
CLLOTObjectRemarketingList
OBJECT_REMARKETING_LIST
CLLOTObjectRichmediaCreative
OBJECT_RICHMEDIA_CREATIVE
CLLOTObjectSdSite
OBJECT_SD_SITE
CLLOTObjectSize
OBJECT_SIZE
CLLOTObjectSubAccount
OBJECT_SUBACCOUNT
CLLOTObjectUserProFile
OBJECT_USER_PROFILE
CLLOTObjectUserProFileFilter
OBJECT_USER_PROFILE_FILTER
CLLOTObjectUserRole
OBJECT_USER_ROLE

Instances

Enum ChangeLogsListObjectType Source # 
Eq ChangeLogsListObjectType Source # 
Data ChangeLogsListObjectType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChangeLogsListObjectType -> c ChangeLogsListObjectType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChangeLogsListObjectType #

toConstr :: ChangeLogsListObjectType -> Constr #

dataTypeOf :: ChangeLogsListObjectType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChangeLogsListObjectType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChangeLogsListObjectType) #

gmapT :: (forall b. Data b => b -> b) -> ChangeLogsListObjectType -> ChangeLogsListObjectType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChangeLogsListObjectType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChangeLogsListObjectType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChangeLogsListObjectType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChangeLogsListObjectType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChangeLogsListObjectType -> m ChangeLogsListObjectType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeLogsListObjectType -> m ChangeLogsListObjectType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeLogsListObjectType -> m ChangeLogsListObjectType #

Ord ChangeLogsListObjectType Source # 
Read ChangeLogsListObjectType Source # 
Show ChangeLogsListObjectType Source # 
Generic ChangeLogsListObjectType Source # 
Hashable ChangeLogsListObjectType Source # 
ToJSON ChangeLogsListObjectType Source # 
FromJSON ChangeLogsListObjectType Source # 
FromHttpApiData ChangeLogsListObjectType Source # 
ToHttpApiData ChangeLogsListObjectType Source # 
type Rep ChangeLogsListObjectType Source # 
type Rep ChangeLogsListObjectType = D1 (MetaData "ChangeLogsListObjectType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CLLOTObjectAccount" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectAccountBillingFeature" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CLLOTObjectAd" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectAdvertiser" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CLLOTObjectAdvertiserGroup" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectBillingAccountGroup" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CLLOTObjectBillingFeature" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLLOTObjectBillingMinimumFee" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectBillingProFile" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CLLOTObjectCampaign" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectContentCategory" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CLLOTObjectCreative" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectCreativeAsset" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CLLOTObjectCreativeBundle" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectCreativeField" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CLLOTObjectCreativeGroup" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLLOTObjectDfaSite" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectEventTag" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CLLOTObjectFloodlightActivityGroup" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectFloodlightActvity" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CLLOTObjectFloodlightConfiguration" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectInstreamCreative" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CLLOTObjectLandingPage" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectMediaOrder" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CLLOTObjectPlacement" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLLOTObjectPlacementStrategy" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectPlaystoreLink" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CLLOTObjectProvidedListClient" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectRateCard" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CLLOTObjectRemarketingList" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLLOTObjectRichmediaCreative" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectSdSite" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "CLLOTObjectSize" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectSubAccount" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CLLOTObjectUserProFile" PrefixI False) U1) ((:+:) (C1 (MetaCons "CLLOTObjectUserProFileFilter" PrefixI False) U1) (C1 (MetaCons "CLLOTObjectUserRole" PrefixI False) U1)))))))

OrderContact

data OrderContact Source #

Contact of an order.

See: orderContact smart constructor.

Instances

Eq OrderContact Source # 
Data OrderContact Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderContact -> c OrderContact #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderContact #

toConstr :: OrderContact -> Constr #

dataTypeOf :: OrderContact -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderContact) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderContact) #

gmapT :: (forall b. Data b => b -> b) -> OrderContact -> OrderContact #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderContact -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderContact -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderContact -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderContact -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderContact -> m OrderContact #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderContact -> m OrderContact #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderContact -> m OrderContact #

Show OrderContact Source # 
Generic OrderContact Source # 

Associated Types

type Rep OrderContact :: * -> * #

ToJSON OrderContact Source # 
FromJSON OrderContact Source # 
type Rep OrderContact Source # 
type Rep OrderContact = D1 (MetaData "OrderContact" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "OrderContact'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ocSignatureUserProFileId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_ocContactName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ocContactTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ocContactType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe OrderContactContactType))) (S1 (MetaSel (Just Symbol "_ocContactInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

orderContact :: OrderContact Source #

Creates a value of OrderContact with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ocSignatureUserProFileId :: Lens' OrderContact (Maybe Int64) Source #

ID of the user profile containing the signature that will be embedded into order documents.

ocContactName :: Lens' OrderContact (Maybe Text) Source #

Name of this contact.

ocContactTitle :: Lens' OrderContact (Maybe Text) Source #

Title of this contact.

ocContactInfo :: Lens' OrderContact (Maybe Text) Source #

Free-form information about this contact. It could be any information related to this contact in addition to type, title, name, and signature user profile ID.

FloodlightActivitiesGenerateTagResponse

data FloodlightActivitiesGenerateTagResponse Source #

Floodlight Activity GenerateTag Response

See: floodlightActivitiesGenerateTagResponse smart constructor.

Instances

Eq FloodlightActivitiesGenerateTagResponse Source # 
Data FloodlightActivitiesGenerateTagResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivitiesGenerateTagResponse -> c FloodlightActivitiesGenerateTagResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivitiesGenerateTagResponse #

toConstr :: FloodlightActivitiesGenerateTagResponse -> Constr #

dataTypeOf :: FloodlightActivitiesGenerateTagResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivitiesGenerateTagResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivitiesGenerateTagResponse) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivitiesGenerateTagResponse -> FloodlightActivitiesGenerateTagResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivitiesGenerateTagResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivitiesGenerateTagResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivitiesGenerateTagResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivitiesGenerateTagResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivitiesGenerateTagResponse -> m FloodlightActivitiesGenerateTagResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivitiesGenerateTagResponse -> m FloodlightActivitiesGenerateTagResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivitiesGenerateTagResponse -> m FloodlightActivitiesGenerateTagResponse #

Show FloodlightActivitiesGenerateTagResponse Source # 
Generic FloodlightActivitiesGenerateTagResponse Source # 
ToJSON FloodlightActivitiesGenerateTagResponse Source # 
FromJSON FloodlightActivitiesGenerateTagResponse Source # 
type Rep FloodlightActivitiesGenerateTagResponse Source # 
type Rep FloodlightActivitiesGenerateTagResponse = D1 (MetaData "FloodlightActivitiesGenerateTagResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "FloodlightActivitiesGenerateTagResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fagtrFloodlightActivityTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_fagtrKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

floodlightActivitiesGenerateTagResponse :: FloodlightActivitiesGenerateTagResponse Source #

Creates a value of FloodlightActivitiesGenerateTagResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

fagtrKind :: Lens' FloodlightActivitiesGenerateTagResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#floodlightActivitiesGenerateTagResponse".

DirectorySiteContactAssignment

data DirectorySiteContactAssignment Source #

Directory Site Contact Assignment

See: directorySiteContactAssignment smart constructor.

Instances

Eq DirectorySiteContactAssignment Source # 
Data DirectorySiteContactAssignment Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectorySiteContactAssignment -> c DirectorySiteContactAssignment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectorySiteContactAssignment #

toConstr :: DirectorySiteContactAssignment -> Constr #

dataTypeOf :: DirectorySiteContactAssignment -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectorySiteContactAssignment) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectorySiteContactAssignment) #

gmapT :: (forall b. Data b => b -> b) -> DirectorySiteContactAssignment -> DirectorySiteContactAssignment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteContactAssignment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectorySiteContactAssignment -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectorySiteContactAssignment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectorySiteContactAssignment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectorySiteContactAssignment -> m DirectorySiteContactAssignment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteContactAssignment -> m DirectorySiteContactAssignment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectorySiteContactAssignment -> m DirectorySiteContactAssignment #

Show DirectorySiteContactAssignment Source # 
Generic DirectorySiteContactAssignment Source # 
ToJSON DirectorySiteContactAssignment Source # 
FromJSON DirectorySiteContactAssignment Source # 
type Rep DirectorySiteContactAssignment Source # 
type Rep DirectorySiteContactAssignment = D1 (MetaData "DirectorySiteContactAssignment" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DirectorySiteContactAssignment'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dscaVisibility") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DirectorySiteContactAssignmentVisibility))) (S1 (MetaSel (Just Symbol "_dscaContactId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))

directorySiteContactAssignment :: DirectorySiteContactAssignment Source #

Creates a value of DirectorySiteContactAssignment with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dscaVisibility :: Lens' DirectorySiteContactAssignment (Maybe DirectorySiteContactAssignmentVisibility) Source #

Visibility of this directory site contact assignment. When set to PUBLIC this contact assignment is visible to all account and agency users; when set to PRIVATE it is visible only to the site.

dscaContactId :: Lens' DirectorySiteContactAssignment (Maybe Int64) Source #

ID of this directory site contact. This is a read-only, auto-generated field.

AdSlot

data AdSlot Source #

Ad Slot

See: adSlot smart constructor.

Instances

Eq AdSlot Source # 

Methods

(==) :: AdSlot -> AdSlot -> Bool #

(/=) :: AdSlot -> AdSlot -> Bool #

Data AdSlot Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdSlot -> c AdSlot #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdSlot #

toConstr :: AdSlot -> Constr #

dataTypeOf :: AdSlot -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdSlot) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdSlot) #

gmapT :: (forall b. Data b => b -> b) -> AdSlot -> AdSlot #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdSlot -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdSlot -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdSlot -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdSlot -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdSlot -> m AdSlot #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdSlot -> m AdSlot #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdSlot -> m AdSlot #

Show AdSlot Source # 
Generic AdSlot Source # 

Associated Types

type Rep AdSlot :: * -> * #

Methods

from :: AdSlot -> Rep AdSlot x #

to :: Rep AdSlot x -> AdSlot #

ToJSON AdSlot Source # 
FromJSON AdSlot Source # 
type Rep AdSlot Source # 

adSlot :: AdSlot Source #

Creates a value of AdSlot with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

assHeight :: Lens' AdSlot (Maybe Int64) Source #

Height of this ad slot.

assPaymentSourceType :: Lens' AdSlot (Maybe AdSlotPaymentSourceType) Source #

Payment source type of this ad slot.

assLinkedPlacementId :: Lens' AdSlot (Maybe Int64) Source #

ID of the placement from an external platform that is linked to this ad slot.

assWidth :: Lens' AdSlot (Maybe Int64) Source #

Width of this ad slot.

assPrimary :: Lens' AdSlot (Maybe Bool) Source #

Primary ad slot of a roadblock inventory item.

assName :: Lens' AdSlot (Maybe Text) Source #

Name of this ad slot.

assComment :: Lens' AdSlot (Maybe Text) Source #

Comment for this ad slot.

assCompatibility :: Lens' AdSlot (Maybe AdSlotCompatibility) Source #

Ad slot compatibility. DISPLAY and DISPLAY_INTERSTITIAL refer to rendering either on desktop, mobile devices or in mobile apps for regular or interstitial ads respectively. APP and APP_INTERSTITIAL are for rendering in mobile apps. IN_STREAM_VIDEO refers to rendering in in-stream video ads developed with the VAST standard.

ThirdPartyTrackingURL

data ThirdPartyTrackingURL Source #

Third-party Tracking URL.

See: thirdPartyTrackingURL smart constructor.

Instances

Eq ThirdPartyTrackingURL Source # 
Data ThirdPartyTrackingURL Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ThirdPartyTrackingURL -> c ThirdPartyTrackingURL #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ThirdPartyTrackingURL #

toConstr :: ThirdPartyTrackingURL -> Constr #

dataTypeOf :: ThirdPartyTrackingURL -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ThirdPartyTrackingURL) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ThirdPartyTrackingURL) #

gmapT :: (forall b. Data b => b -> b) -> ThirdPartyTrackingURL -> ThirdPartyTrackingURL #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ThirdPartyTrackingURL -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ThirdPartyTrackingURL -> r #

gmapQ :: (forall d. Data d => d -> u) -> ThirdPartyTrackingURL -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ThirdPartyTrackingURL -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ThirdPartyTrackingURL -> m ThirdPartyTrackingURL #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ThirdPartyTrackingURL -> m ThirdPartyTrackingURL #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ThirdPartyTrackingURL -> m ThirdPartyTrackingURL #

Show ThirdPartyTrackingURL Source # 
Generic ThirdPartyTrackingURL Source # 
ToJSON ThirdPartyTrackingURL Source # 
FromJSON ThirdPartyTrackingURL Source # 
type Rep ThirdPartyTrackingURL Source # 
type Rep ThirdPartyTrackingURL = D1 (MetaData "ThirdPartyTrackingURL" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "ThirdPartyTrackingURL'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tptuURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tptuThirdPartyURLType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ThirdPartyTrackingURLThirdPartyURLType)))))

thirdPartyTrackingURL :: ThirdPartyTrackingURL Source #

Creates a value of ThirdPartyTrackingURL with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tptuURL :: Lens' ThirdPartyTrackingURL (Maybe Text) Source #

URL for the specified third-party URL type.

PricingCapCostType

data PricingCapCostType Source #

Cap cost type of this inventory item.

Constructors

PlanningPlacementCapCostTypeCumulative
PLANNING_PLACEMENT_CAP_COST_TYPE_CUMULATIVE
PlanningPlacementCapCostTypeMonthly
PLANNING_PLACEMENT_CAP_COST_TYPE_MONTHLY
PlanningPlacementCapCostTypeNone
PLANNING_PLACEMENT_CAP_COST_TYPE_NONE

Instances

Enum PricingCapCostType Source # 
Eq PricingCapCostType Source # 
Data PricingCapCostType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PricingCapCostType -> c PricingCapCostType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PricingCapCostType #

toConstr :: PricingCapCostType -> Constr #

dataTypeOf :: PricingCapCostType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PricingCapCostType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PricingCapCostType) #

gmapT :: (forall b. Data b => b -> b) -> PricingCapCostType -> PricingCapCostType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PricingCapCostType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PricingCapCostType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PricingCapCostType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PricingCapCostType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PricingCapCostType -> m PricingCapCostType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PricingCapCostType -> m PricingCapCostType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PricingCapCostType -> m PricingCapCostType #

Ord PricingCapCostType Source # 
Read PricingCapCostType Source # 
Show PricingCapCostType Source # 
Generic PricingCapCostType Source # 
Hashable PricingCapCostType Source # 
ToJSON PricingCapCostType Source # 
FromJSON PricingCapCostType Source # 
FromHttpApiData PricingCapCostType Source # 
ToHttpApiData PricingCapCostType Source # 
type Rep PricingCapCostType Source # 
type Rep PricingCapCostType = D1 (MetaData "PricingCapCostType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "PlanningPlacementCapCostTypeCumulative" PrefixI False) U1) ((:+:) (C1 (MetaCons "PlanningPlacementCapCostTypeMonthly" PrefixI False) U1) (C1 (MetaCons "PlanningPlacementCapCostTypeNone" PrefixI False) U1)))

OrderDocument

data OrderDocument Source #

Contains properties of a DoubleClick Planning order document.

See: orderDocument smart constructor.

Instances

Eq OrderDocument Source # 
Data OrderDocument Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderDocument -> c OrderDocument #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderDocument #

toConstr :: OrderDocument -> Constr #

dataTypeOf :: OrderDocument -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OrderDocument) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderDocument) #

gmapT :: (forall b. Data b => b -> b) -> OrderDocument -> OrderDocument #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderDocument -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderDocument -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderDocument -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderDocument -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderDocument -> m OrderDocument #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderDocument -> m OrderDocument #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderDocument -> m OrderDocument #

Show OrderDocument Source # 
Generic OrderDocument Source # 

Associated Types

type Rep OrderDocument :: * -> * #

ToJSON OrderDocument Source # 
FromJSON OrderDocument Source # 
type Rep OrderDocument Source # 
type Rep OrderDocument = D1 (MetaData "OrderDocument" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "OrderDocument'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_odSigned") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_odKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_odAdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_odLastSentTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_odAmendedOrderDocumentId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_odLastSentRecipients") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))) ((:*:) (S1 (MetaSel (Just Symbol "_odEffectiveDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Date'))) (S1 (MetaSel (Just Symbol "_odApprovedByUserProFileIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64])))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_odAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_odId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_odProjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_odTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_odSubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_odType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe OrderDocumentType)))) ((:*:) (S1 (MetaSel (Just Symbol "_odOrderId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_odCancelled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_odCreatedInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo)))))))))

odSigned :: Lens' OrderDocument (Maybe Bool) Source #

Whether this order document has been signed.

odKind :: Lens' OrderDocument Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#orderDocument".

odAdvertiserId :: Lens' OrderDocument (Maybe Int64) Source #

Advertiser ID of this order document.

odLastSentTime :: Lens' OrderDocument (Maybe UTCTime) Source #

Timestamp of the last email sent with this order document.

odAmendedOrderDocumentId :: Lens' OrderDocument (Maybe Int64) Source #

The amended order document ID of this order document. An order document can be created by optionally amending another order document so that the change history can be preserved.

odLastSentRecipients :: Lens' OrderDocument [Text] Source #

List of email addresses that received the last sent document.

odEffectiveDate :: Lens' OrderDocument (Maybe Day) Source #

Effective date of this order document.

odApprovedByUserProFileIds :: Lens' OrderDocument [Int64] Source #

IDs of users who have approved this order document.

odAccountId :: Lens' OrderDocument (Maybe Int64) Source #

Account ID of this order document.

odId :: Lens' OrderDocument (Maybe Int64) Source #

ID of this order document.

odProjectId :: Lens' OrderDocument (Maybe Int64) Source #

Project ID of this order document.

odTitle :: Lens' OrderDocument (Maybe Text) Source #

Title of this order document.

odSubAccountId :: Lens' OrderDocument (Maybe Int64) Source #

Subaccount ID of this order document.

odType :: Lens' OrderDocument (Maybe OrderDocumentType) Source #

Type of this order document

odOrderId :: Lens' OrderDocument (Maybe Int64) Source #

ID of the order from which this order document is created.

odCancelled :: Lens' OrderDocument (Maybe Bool) Source #

Whether this order document is cancelled.

odCreatedInfo :: Lens' OrderDocument (Maybe LastModifiedInfo) Source #

Information about the creation of this order document.

Metro

data Metro Source #

Contains information about a metro region that can be targeted by ads.

See: metro smart constructor.

Instances

Eq Metro Source # 

Methods

(==) :: Metro -> Metro -> Bool #

(/=) :: Metro -> Metro -> Bool #

Data Metro Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Metro -> c Metro #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Metro #

toConstr :: Metro -> Constr #

dataTypeOf :: Metro -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Metro) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Metro) #

gmapT :: (forall b. Data b => b -> b) -> Metro -> Metro #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Metro -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Metro -> r #

gmapQ :: (forall d. Data d => d -> u) -> Metro -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Metro -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Metro -> m Metro #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Metro -> m Metro #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Metro -> m Metro #

Show Metro Source # 

Methods

showsPrec :: Int -> Metro -> ShowS #

show :: Metro -> String #

showList :: [Metro] -> ShowS #

Generic Metro Source # 

Associated Types

type Rep Metro :: * -> * #

Methods

from :: Metro -> Rep Metro x #

to :: Rep Metro x -> Metro #

ToJSON Metro Source # 
FromJSON Metro Source # 
type Rep Metro Source # 

metro :: Metro Source #

Creates a value of Metro with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

metMetroCode :: Lens' Metro (Maybe Text) Source #

Metro code of this metro region. This is equivalent to dma_id.

metKind :: Lens' Metro Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#metro".

metName :: Lens' Metro (Maybe Text) Source #

Name of this metro region.

metCountryCode :: Lens' Metro (Maybe Text) Source #

Country code of the country to which this metro region belongs.

metDmaId :: Lens' Metro (Maybe Int64) Source #

DMA ID of this metro region. This is the ID used for targeting and generating reports, and is equivalent to metro_code.

metCountryDartId :: Lens' Metro (Maybe Int64) Source #

DART ID of the country to which this metro region belongs.

metDartId :: Lens' Metro (Maybe Int64) Source #

DART ID of this metro region.

CreativeAssetDisplayType

data CreativeAssetDisplayType Source #

Type of rich media asset. This is a read-only field. Applicable to the following creative types: all RICH_MEDIA.

Constructors

AssetDisplayTypeExpanding
ASSET_DISPLAY_TYPE_EXPANDING
AssetDisplayTypeFlashInFlash
ASSET_DISPLAY_TYPE_FLASH_IN_FLASH
AssetDisplayTypeFlashInFlashExpanding
ASSET_DISPLAY_TYPE_FLASH_IN_FLASH_EXPANDING
AssetDisplayTypeFloating
ASSET_DISPLAY_TYPE_FLOATING
AssetDisplayTypeInpage
ASSET_DISPLAY_TYPE_INPAGE
AssetDisplayTypeOverlay
ASSET_DISPLAY_TYPE_OVERLAY
AssetDisplayTypePeelDown
ASSET_DISPLAY_TYPE_PEEL_DOWN
AssetDisplayTypeVpaidLinear
ASSET_DISPLAY_TYPE_VPAID_LINEAR
AssetDisplayTypeVpaidNonLinear
ASSET_DISPLAY_TYPE_VPAID_NON_LINEAR

Instances

Enum CreativeAssetDisplayType Source # 
Eq CreativeAssetDisplayType Source # 
Data CreativeAssetDisplayType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeAssetDisplayType -> c CreativeAssetDisplayType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeAssetDisplayType #

toConstr :: CreativeAssetDisplayType -> Constr #

dataTypeOf :: CreativeAssetDisplayType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeAssetDisplayType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeAssetDisplayType) #

gmapT :: (forall b. Data b => b -> b) -> CreativeAssetDisplayType -> CreativeAssetDisplayType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetDisplayType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeAssetDisplayType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeAssetDisplayType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeAssetDisplayType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeAssetDisplayType -> m CreativeAssetDisplayType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetDisplayType -> m CreativeAssetDisplayType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeAssetDisplayType -> m CreativeAssetDisplayType #

Ord CreativeAssetDisplayType Source # 
Read CreativeAssetDisplayType Source # 
Show CreativeAssetDisplayType Source # 
Generic CreativeAssetDisplayType Source # 
Hashable CreativeAssetDisplayType Source # 
ToJSON CreativeAssetDisplayType Source # 
FromJSON CreativeAssetDisplayType Source # 
FromHttpApiData CreativeAssetDisplayType Source # 
ToHttpApiData CreativeAssetDisplayType Source # 
type Rep CreativeAssetDisplayType Source # 
type Rep CreativeAssetDisplayType = D1 (MetaData "CreativeAssetDisplayType" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "AssetDisplayTypeExpanding" PrefixI False) U1) (C1 (MetaCons "AssetDisplayTypeFlashInFlash" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AssetDisplayTypeFlashInFlashExpanding" PrefixI False) U1) (C1 (MetaCons "AssetDisplayTypeFloating" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "AssetDisplayTypeInpage" PrefixI False) U1) (C1 (MetaCons "AssetDisplayTypeOverlay" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AssetDisplayTypePeelDown" PrefixI False) U1) ((:+:) (C1 (MetaCons "AssetDisplayTypeVpaidLinear" PrefixI False) U1) (C1 (MetaCons "AssetDisplayTypeVpaidNonLinear" PrefixI False) U1)))))

Placement

data Placement Source #

Contains properties of a placement.

See: placement smart constructor.

Instances

Eq Placement Source # 
Data Placement Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Placement -> c Placement #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Placement #

toConstr :: Placement -> Constr #

dataTypeOf :: Placement -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Placement) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Placement) #

gmapT :: (forall b. Data b => b -> b) -> Placement -> Placement #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Placement -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Placement -> r #

gmapQ :: (forall d. Data d => d -> u) -> Placement -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Placement -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Placement -> m Placement #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Placement -> m Placement #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Placement -> m Placement #

Show Placement Source # 
Generic Placement Source # 

Associated Types

type Rep Placement :: * -> * #

ToJSON Placement Source # 
FromJSON Placement Source # 
type Rep Placement Source # 
type Rep Placement = D1 (MetaData "Placement" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "Placement'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_p1Status") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PlacementStatus))) (S1 (MetaSel (Just Symbol "_p1PlacementStrategyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) ((:*:) (S1 (MetaSel (Just Symbol "_p1TagFormats") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PlacementTagFormatsItem]))) (S1 (MetaSel (Just Symbol "_p1SiteIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_p1PricingSchedule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PricingSchedule))) (S1 (MetaSel (Just Symbol "_p1Size") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Size)))) ((:*:) (S1 (MetaSel (Just Symbol "_p1Kind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_p1KeyName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_p1CampaignIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_p1AdvertiserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_p1AdvertiserIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue)))) ((:*:) (S1 (MetaSel (Just Symbol "_p1CampaignId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_p1IdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_p1Primary") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_p1LookbackConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LookbackConfiguration)))) ((:*:) (S1 (MetaSel (Just Symbol "_p1TagSetting") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TagSetting))) ((:*:) (S1 (MetaSel (Just Symbol "_p1ContentCategoryId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_p1DirectorySiteIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue)))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_p1AccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_p1PaymentSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PlacementPaymentSource)))) ((:*:) (S1 (MetaSel (Just Symbol "_p1Name") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_p1DirectorySiteId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_p1CreateInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo))) (S1 (MetaSel (Just Symbol "_p1LastModifiedInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo)))) ((:*:) (S1 (MetaSel (Just Symbol "_p1Id") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_p1SSLRequired") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_p1SubAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_p1PlacementGroupIdDimensionValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionValue))) (S1 (MetaSel (Just Symbol "_p1ExternalId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_p1PlacementGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_p1Comment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_p1SiteId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_p1Compatibility") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PlacementCompatibility)))) ((:*:) (S1 (MetaSel (Just Symbol "_p1Archived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_p1PaymentApproved") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_p1PublisherUpdateInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LastModifiedInfo))))))))))

p1Status :: Lens' Placement (Maybe PlacementStatus) Source #

Third-party placement status.

p1PlacementStrategyId :: Lens' Placement (Maybe Int64) Source #

ID of the placement strategy assigned to this placement.

p1TagFormats :: Lens' Placement [PlacementTagFormatsItem] Source #

Tag formats to generate for this placement. This field is required on insertion. Acceptable values are: - "PLACEMENT_TAG_STANDARD" - "PLACEMENT_TAG_IFRAME_JAVASCRIPT" - "PLACEMENT_TAG_IFRAME_ILAYER" - "PLACEMENT_TAG_INTERNAL_REDIRECT" - "PLACEMENT_TAG_JAVASCRIPT" - "PLACEMENT_TAG_INTERSTITIAL_IFRAME_JAVASCRIPT" - "PLACEMENT_TAG_INTERSTITIAL_INTERNAL_REDIRECT" - "PLACEMENT_TAG_INTERSTITIAL_JAVASCRIPT" - "PLACEMENT_TAG_CLICK_COMMANDS" - "PLACEMENT_TAG_INSTREAM_VIDEO_PREFETCH" - "PLACEMENT_TAG_TRACKING" - "PLACEMENT_TAG_TRACKING_IFRAME" - "PLACEMENT_TAG_TRACKING_JAVASCRIPT"

p1SiteIdDimensionValue :: Lens' Placement (Maybe DimensionValue) Source #

Dimension value for the ID of the site. This is a read-only, auto-generated field.

p1PricingSchedule :: Lens' Placement (Maybe PricingSchedule) Source #

Pricing schedule of this placement. This field is required on insertion, specifically subfields startDate, endDate and pricingType.

p1Size :: Lens' Placement (Maybe Size) Source #

Size associated with this placement. When inserting or updating a placement, only the size ID field is used. This field is required on insertion.

p1Kind :: Lens' Placement Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#placement".

p1KeyName :: Lens' Placement (Maybe Text) Source #

Key name of this placement. This is a read-only, auto-generated field.

p1CampaignIdDimensionValue :: Lens' Placement (Maybe DimensionValue) Source #

Dimension value for the ID of the campaign. This is a read-only, auto-generated field.

p1AdvertiserId :: Lens' Placement (Maybe Int64) Source #

Advertiser ID of this placement. This field can be left blank.

p1AdvertiserIdDimensionValue :: Lens' Placement (Maybe DimensionValue) Source #

Dimension value for the ID of the advertiser. This is a read-only, auto-generated field.

p1CampaignId :: Lens' Placement (Maybe Int64) Source #

Campaign ID of this placement. This field is a required field on insertion.

p1IdDimensionValue :: Lens' Placement (Maybe DimensionValue) Source #

Dimension value for the ID of this placement. This is a read-only, auto-generated field.

p1Primary :: Lens' Placement (Maybe Bool) Source #

Whether this placement is the primary placement of a roadblock (placement group). You cannot change this field from true to false. Setting this field to true will automatically set the primary field on the original primary placement of the roadblock to false, and it will automatically set the roadblock's primaryPlacementId field to the ID of this placement.

p1LookbackConfiguration :: Lens' Placement (Maybe LookbackConfiguration) Source #

Lookback window settings for this placement.

p1TagSetting :: Lens' Placement (Maybe TagSetting) Source #

Tag settings for this placement.

p1ContentCategoryId :: Lens' Placement (Maybe Int64) Source #

ID of the content category assigned to this placement.

p1DirectorySiteIdDimensionValue :: Lens' Placement (Maybe DimensionValue) Source #

Dimension value for the ID of the directory site. This is a read-only, auto-generated field.

p1AccountId :: Lens' Placement (Maybe Int64) Source #

Account ID of this placement. This field can be left blank.

p1PaymentSource :: Lens' Placement (Maybe PlacementPaymentSource) Source #

Payment source for this placement. This is a required field that is read-only after insertion.

p1Name :: Lens' Placement (Maybe Text) Source #

Name of this placement.This is a required field and must be less than 256 characters long.

p1DirectorySiteId :: Lens' Placement (Maybe Int64) Source #

Directory site ID of this placement. On insert, you must set either this field or the siteId field to specify the site associated with this placement. This is a required field that is read-only after insertion.

p1CreateInfo :: Lens' Placement (Maybe LastModifiedInfo) Source #

Information about the creation of this placement. This is a read-only field.

p1LastModifiedInfo :: Lens' Placement (Maybe LastModifiedInfo) Source #

Information about the most recent modification of this placement. This is a read-only field.

p1Id :: Lens' Placement (Maybe Int64) Source #

ID of this placement. This is a read-only, auto-generated field.

p1SSLRequired :: Lens' Placement (Maybe Bool) Source #

Whether creatives assigned to this placement must be SSL-compliant.

p1SubAccountId :: Lens' Placement (Maybe Int64) Source #

Subaccount ID of this placement. This field can be left blank.

p1PlacementGroupIdDimensionValue :: Lens' Placement (Maybe DimensionValue) Source #

Dimension value for the ID of the placement group. This is a read-only, auto-generated field.

p1ExternalId :: Lens' Placement (Maybe Text) Source #

External ID for this placement.

p1PlacementGroupId :: Lens' Placement (Maybe Int64) Source #

ID of this placement's group, if applicable.

p1Comment :: Lens' Placement (Maybe Text) Source #

Comments for this placement.

p1SiteId :: Lens' Placement (Maybe Int64) Source #

Site ID associated with this placement. On insert, you must set either this field or the directorySiteId field to specify the site associated with this placement. This is a required field that is read-only after insertion.

p1Compatibility :: Lens' Placement (Maybe PlacementCompatibility) Source #

Placement compatibility. DISPLAY and DISPLAY_INTERSTITIAL refer to rendering on desktop, on mobile devices or in mobile apps for regular or interstitial ads respectively. APP and APP_INTERSTITIAL are no longer allowed for new placement insertions. Instead, use DISPLAY or DISPLAY_INTERSTITIAL. IN_STREAM_VIDEO refers to rendering in in-stream video ads developed with the VAST standard. This field is required on insertion.

p1Archived :: Lens' Placement (Maybe Bool) Source #

Whether this placement is archived.

p1PaymentApproved :: Lens' Placement (Maybe Bool) Source #

Whether payment was approved for this placement. This is a read-only field relevant only to publisher-paid placements.

p1PublisherUpdateInfo :: Lens' Placement (Maybe LastModifiedInfo) Source #

Information about the last publisher update. This is a read-only field.

FloodlightActivityCountingMethod

data FloodlightActivityCountingMethod Source #

Counting method for conversions for this floodlight activity. This is a required field.

Constructors

ItemsSoldCounting
ITEMS_SOLD_COUNTING
SessionCounting
SESSION_COUNTING
StandardCounting
STANDARD_COUNTING
TransactionsCounting
TRANSACTIONS_COUNTING
UniqueCounting
UNIQUE_COUNTING

Instances

Enum FloodlightActivityCountingMethod Source # 
Eq FloodlightActivityCountingMethod Source # 
Data FloodlightActivityCountingMethod Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloodlightActivityCountingMethod -> c FloodlightActivityCountingMethod #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloodlightActivityCountingMethod #

toConstr :: FloodlightActivityCountingMethod -> Constr #

dataTypeOf :: FloodlightActivityCountingMethod -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FloodlightActivityCountingMethod) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloodlightActivityCountingMethod) #

gmapT :: (forall b. Data b => b -> b) -> FloodlightActivityCountingMethod -> FloodlightActivityCountingMethod #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityCountingMethod -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloodlightActivityCountingMethod -> r #

gmapQ :: (forall d. Data d => d -> u) -> FloodlightActivityCountingMethod -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloodlightActivityCountingMethod -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloodlightActivityCountingMethod -> m FloodlightActivityCountingMethod #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityCountingMethod -> m FloodlightActivityCountingMethod #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloodlightActivityCountingMethod -> m FloodlightActivityCountingMethod #

Ord FloodlightActivityCountingMethod Source # 
Read FloodlightActivityCountingMethod Source # 
Show FloodlightActivityCountingMethod Source # 
Generic FloodlightActivityCountingMethod Source # 
Hashable FloodlightActivityCountingMethod Source # 
ToJSON FloodlightActivityCountingMethod Source # 
FromJSON FloodlightActivityCountingMethod Source # 
FromHttpApiData FloodlightActivityCountingMethod Source # 
ToHttpApiData FloodlightActivityCountingMethod Source # 
type Rep FloodlightActivityCountingMethod Source # 
type Rep FloodlightActivityCountingMethod = D1 (MetaData "FloodlightActivityCountingMethod" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) ((:+:) (C1 (MetaCons "ItemsSoldCounting" PrefixI False) U1) (C1 (MetaCons "SessionCounting" PrefixI False) U1)) ((:+:) (C1 (MetaCons "StandardCounting" PrefixI False) U1) ((:+:) (C1 (MetaCons "TransactionsCounting" PrefixI False) U1) (C1 (MetaCons "UniqueCounting" PrefixI False) U1))))

EncryptionInfo

data EncryptionInfo Source #

A description of how user IDs are encrypted.

See: encryptionInfo smart constructor.

Instances

Eq EncryptionInfo Source # 
Data EncryptionInfo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EncryptionInfo -> c EncryptionInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EncryptionInfo #

toConstr :: EncryptionInfo -> Constr #

dataTypeOf :: EncryptionInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EncryptionInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EncryptionInfo) #

gmapT :: (forall b. Data b => b -> b) -> EncryptionInfo -> EncryptionInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EncryptionInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EncryptionInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> EncryptionInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EncryptionInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EncryptionInfo -> m EncryptionInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EncryptionInfo -> m EncryptionInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EncryptionInfo -> m EncryptionInfo #

Show EncryptionInfo Source # 
Generic EncryptionInfo Source # 

Associated Types

type Rep EncryptionInfo :: * -> * #

ToJSON EncryptionInfo Source # 
FromJSON EncryptionInfo Source # 
type Rep EncryptionInfo Source # 
type Rep EncryptionInfo = D1 (MetaData "EncryptionInfo" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "EncryptionInfo'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_eiEncryptionSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EncryptionInfoEncryptionSource))) (S1 (MetaSel (Just Symbol "_eiKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_eiEncryptionEntityType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EncryptionInfoEncryptionEntityType))) (S1 (MetaSel (Just Symbol "_eiEncryptionEntityId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))))))

encryptionInfo :: EncryptionInfo Source #

Creates a value of EncryptionInfo with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

eiEncryptionSource :: Lens' EncryptionInfo (Maybe EncryptionInfoEncryptionSource) Source #

Describes whether the encrypted cookie was received from ad serving (the %m macro) or from Data Transfer.

eiKind :: Lens' EncryptionInfo Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#encryptionInfo".

eiEncryptionEntityType :: Lens' EncryptionInfo (Maybe EncryptionInfoEncryptionEntityType) Source #

The encryption entity type. This should match the encryption configuration for ad serving or Data Transfer.

eiEncryptionEntityId :: Lens' EncryptionInfo (Maybe Int64) Source #

The encryption entity ID. This should match the encryption configuration for ad serving or Data Transfer.

SitesListResponse

data SitesListResponse Source #

Site List Response

See: sitesListResponse smart constructor.

Instances

Eq SitesListResponse Source # 
Data SitesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SitesListResponse -> c SitesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SitesListResponse #

toConstr :: SitesListResponse -> Constr #

dataTypeOf :: SitesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SitesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SitesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> SitesListResponse -> SitesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SitesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SitesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> SitesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SitesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SitesListResponse -> m SitesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SitesListResponse -> m SitesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SitesListResponse -> m SitesListResponse #

Show SitesListResponse Source # 
Generic SitesListResponse Source # 
ToJSON SitesListResponse Source # 
FromJSON SitesListResponse Source # 
type Rep SitesListResponse Source # 
type Rep SitesListResponse = D1 (MetaData "SitesListResponse" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "SitesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sitNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sitKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_sitSites") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Site]))))))

sitesListResponse :: SitesListResponse Source #

Creates a value of SitesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sitNextPageToken :: Lens' SitesListResponse (Maybe Text) Source #

Pagination token to be used for the next list operation.

sitKind :: Lens' SitesListResponse Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#sitesListResponse".

ContentCategoriesListSortOrder

data ContentCategoriesListSortOrder Source #

Order of sorted results, default is ASCENDING.

Constructors

CCLSOAscending
ASCENDING
CCLSODescending
DESCENDING

Instances

Enum ContentCategoriesListSortOrder Source # 
Eq ContentCategoriesListSortOrder Source # 
Data ContentCategoriesListSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ContentCategoriesListSortOrder -> c ContentCategoriesListSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ContentCategoriesListSortOrder #

toConstr :: ContentCategoriesListSortOrder -> Constr #

dataTypeOf :: ContentCategoriesListSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ContentCategoriesListSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ContentCategoriesListSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> ContentCategoriesListSortOrder -> ContentCategoriesListSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ContentCategoriesListSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ContentCategoriesListSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> ContentCategoriesListSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ContentCategoriesListSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ContentCategoriesListSortOrder -> m ContentCategoriesListSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ContentCategoriesListSortOrder -> m ContentCategoriesListSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ContentCategoriesListSortOrder -> m ContentCategoriesListSortOrder #

Ord ContentCategoriesListSortOrder Source # 
Read ContentCategoriesListSortOrder Source # 
Show ContentCategoriesListSortOrder Source # 
Generic ContentCategoriesListSortOrder Source # 
Hashable ContentCategoriesListSortOrder Source # 
ToJSON ContentCategoriesListSortOrder Source # 
FromJSON ContentCategoriesListSortOrder Source # 
FromHttpApiData ContentCategoriesListSortOrder Source # 
ToHttpApiData ContentCategoriesListSortOrder Source # 
type Rep ContentCategoriesListSortOrder Source # 
type Rep ContentCategoriesListSortOrder = D1 (MetaData "ContentCategoriesListSortOrder" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "CCLSOAscending" PrefixI False) U1) (C1 (MetaCons "CCLSODescending" PrefixI False) U1))

CreativeField

data CreativeField Source #

Contains properties of a creative field.

See: creativeField smart constructor.

Instances

Eq CreativeField Source # 
Data CreativeField Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreativeField -> c CreativeField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreativeField #

toConstr :: CreativeField -> Constr #

dataTypeOf :: CreativeField -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreativeField) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreativeField) #

gmapT :: (forall b. Data b => b -> b) -> CreativeField -> CreativeField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreativeField -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreativeField -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreativeField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreativeField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreativeField -> m CreativeField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeField -> m CreativeField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreativeField -> m CreativeField #

Show CreativeField Source # 
Generic CreativeField Source # 

Associated Types

type Rep CreativeField :: * -> * #

ToJSON CreativeField Source # 
FromJSON CreativeField Source # 
type Rep CreativeField Source # 

creativeField :: CreativeField Source #

Creates a value of CreativeField with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cffKind :: Lens' CreativeField Text Source #

Identifies what kind of resource this is. Value: the fixed string "dfareporting#creativeField".

cffAdvertiserId :: Lens' CreativeField (Maybe Int64) Source #

Advertiser ID of this creative field. This is a required field on insertion.

cffAdvertiserIdDimensionValue :: Lens' CreativeField (Maybe DimensionValue) Source #

Dimension value for the ID of the advertiser. This is a read-only, auto-generated field.

cffAccountId :: Lens' CreativeField (Maybe Int64) Source #

Account ID of this creative field. This is a read-only field that can be left blank.

cffName :: Lens' CreativeField (Maybe Text) Source #

Name of this creative field. This is a required field and must be less than 256 characters long and unique among creative fields of the same advertiser.

cffId :: Lens' CreativeField (Maybe Int64) Source #

ID of this creative field. This is a read-only, auto-generated field.

cffSubAccountId :: Lens' CreativeField (Maybe Int64) Source #

Subaccount ID of this creative field. This is a read-only field that can be left blank.

AdvertiserStatus

data AdvertiserStatus Source #

Status of this advertiser.

Constructors

ASApproved
APPROVED
ASOnHold
ON_HOLD

Instances

Enum AdvertiserStatus Source # 
Eq AdvertiserStatus Source # 
Data AdvertiserStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AdvertiserStatus -> c AdvertiserStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AdvertiserStatus #

toConstr :: AdvertiserStatus -> Constr #

dataTypeOf :: AdvertiserStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AdvertiserStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AdvertiserStatus) #

gmapT :: (forall b. Data b => b -> b) -> AdvertiserStatus -> AdvertiserStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AdvertiserStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AdvertiserStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> AdvertiserStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AdvertiserStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AdvertiserStatus -> m AdvertiserStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertiserStatus -> m AdvertiserStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AdvertiserStatus -> m AdvertiserStatus #

Ord AdvertiserStatus Source # 
Read AdvertiserStatus Source # 
Show AdvertiserStatus Source # 
Generic AdvertiserStatus Source # 
Hashable AdvertiserStatus Source # 
ToJSON AdvertiserStatus Source # 
FromJSON AdvertiserStatus Source # 
FromHttpApiData AdvertiserStatus Source # 
ToHttpApiData AdvertiserStatus Source # 
type Rep AdvertiserStatus Source # 
type Rep AdvertiserStatus = D1 (MetaData "AdvertiserStatus" "Network.Google.DFAReporting.Types.Sum" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) ((:+:) (C1 (MetaCons "ASApproved" PrefixI False) U1) (C1 (MetaCons "ASOnHold" PrefixI False) U1))

DefaultClickThroughEventTagProperties

data DefaultClickThroughEventTagProperties Source #

Properties of inheriting and overriding the default click-through event tag. A campaign may override the event tag defined at the advertiser level, and an ad may also override the campaign's setting further.

See: defaultClickThroughEventTagProperties smart constructor.

Instances

Eq DefaultClickThroughEventTagProperties Source # 
Data DefaultClickThroughEventTagProperties Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefaultClickThroughEventTagProperties -> c DefaultClickThroughEventTagProperties #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DefaultClickThroughEventTagProperties #

toConstr :: DefaultClickThroughEventTagProperties -> Constr #

dataTypeOf :: DefaultClickThroughEventTagProperties -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DefaultClickThroughEventTagProperties) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DefaultClickThroughEventTagProperties) #

gmapT :: (forall b. Data b => b -> b) -> DefaultClickThroughEventTagProperties -> DefaultClickThroughEventTagProperties #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultClickThroughEventTagProperties -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultClickThroughEventTagProperties -> r #

gmapQ :: (forall d. Data d => d -> u) -> DefaultClickThroughEventTagProperties -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultClickThroughEventTagProperties -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultClickThroughEventTagProperties -> m DefaultClickThroughEventTagProperties #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultClickThroughEventTagProperties -> m DefaultClickThroughEventTagProperties #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultClickThroughEventTagProperties -> m DefaultClickThroughEventTagProperties #

Show DefaultClickThroughEventTagProperties Source # 
Generic DefaultClickThroughEventTagProperties Source # 
ToJSON DefaultClickThroughEventTagProperties Source # 
FromJSON DefaultClickThroughEventTagProperties Source # 
type Rep DefaultClickThroughEventTagProperties Source # 
type Rep DefaultClickThroughEventTagProperties = D1 (MetaData "DefaultClickThroughEventTagProperties" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" False) (C1 (MetaCons "DefaultClickThroughEventTagProperties'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dctetpOverrideInheritedEventTag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_dctetpDefaultClickThroughEventTagId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))))

defaultClickThroughEventTagProperties :: DefaultClickThroughEventTagProperties Source #

Creates a value of DefaultClickThroughEventTagProperties with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dctetpOverrideInheritedEventTag :: Lens' DefaultClickThroughEventTagProperties (Maybe Bool) Source #

Whether this entity should override the inherited default click-through event tag with its own defined value.

dctetpDefaultClickThroughEventTagId :: Lens' DefaultClickThroughEventTagProperties (Maybe Int64) Source #

ID of the click-through event tag to apply to all ads in this entity's scope.

ListTargetingExpression

data ListTargetingExpression Source #

Remarketing List Targeting Expression.

See: listTargetingExpression smart constructor.

Instances

Eq ListTargetingExpression Source # 
Data ListTargetingExpression Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListTargetingExpression -> c ListTargetingExpression #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ListTargetingExpression #

toConstr :: ListTargetingExpression -> Constr #

dataTypeOf :: ListTargetingExpression -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ListTargetingExpression) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListTargetingExpression) #

gmapT :: (forall b. Data b => b -> b) -> ListTargetingExpression -> ListTargetingExpression #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListTargetingExpression -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListTargetingExpression -> r #

gmapQ :: (forall d. Data d => d -> u) -> ListTargetingExpression -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ListTargetingExpression -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ListTargetingExpression -> m ListTargetingExpression #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ListTargetingExpression -> m ListTargetingExpression #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListTargetingExpression -> m ListTargetingExpression #

Show ListTargetingExpression Source # 
Generic ListTargetingExpression Source # 
ToJSON ListTargetingExpression Source # 
FromJSON ListTargetingExpression Source # 
type Rep ListTargetingExpression Source # 
type Rep ListTargetingExpression = D1 (MetaData "ListTargetingExpression" "Network.Google.DFAReporting.Types.Product" "gogol-dfareporting-0.1.0-KEBAT3IXpFyJcea2FOz34a" True) (C1 (MetaCons "ListTargetingExpression'" PrefixI True) (S1 (MetaSel (Just Symbol "_lteExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

listTargetingExpression :: ListTargetingExpression Source #

Creates a value of ListTargetingExpression with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lteExpression :: Lens' ListTargetingExpression (Maybe Text) Source #

Expression describing which lists are being targeted by the ad.