module Network.Google.AdExchangeBuyer.Types.Product where
import Network.Google.AdExchangeBuyer.Types.Sum
import Network.Google.Prelude
data MarketplaceNote = MarketplaceNote'
{ _mnNote :: !(Maybe Text)
, _mnKind :: !Text
, _mnTimestampMs :: !(Maybe (Textual Int64))
, _mnProposalId :: !(Maybe Text)
, _mnDealId :: !(Maybe Text)
, _mnProposalRevisionNumber :: !(Maybe (Textual Int64))
, _mnNoteId :: !(Maybe Text)
, _mnCreatorRole :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
marketplaceNote
:: MarketplaceNote
marketplaceNote =
MarketplaceNote'
{ _mnNote = Nothing
, _mnKind = "adexchangebuyer#marketplaceNote"
, _mnTimestampMs = Nothing
, _mnProposalId = Nothing
, _mnDealId = Nothing
, _mnProposalRevisionNumber = Nothing
, _mnNoteId = Nothing
, _mnCreatorRole = Nothing
}
mnNote :: Lens' MarketplaceNote (Maybe Text)
mnNote = lens _mnNote (\ s a -> s{_mnNote = a})
mnKind :: Lens' MarketplaceNote Text
mnKind = lens _mnKind (\ s a -> s{_mnKind = a})
mnTimestampMs :: Lens' MarketplaceNote (Maybe Int64)
mnTimestampMs
= lens _mnTimestampMs
(\ s a -> s{_mnTimestampMs = a})
. mapping _Coerce
mnProposalId :: Lens' MarketplaceNote (Maybe Text)
mnProposalId
= lens _mnProposalId (\ s a -> s{_mnProposalId = a})
mnDealId :: Lens' MarketplaceNote (Maybe Text)
mnDealId = lens _mnDealId (\ s a -> s{_mnDealId = a})
mnProposalRevisionNumber :: Lens' MarketplaceNote (Maybe Int64)
mnProposalRevisionNumber
= lens _mnProposalRevisionNumber
(\ s a -> s{_mnProposalRevisionNumber = a})
. mapping _Coerce
mnNoteId :: Lens' MarketplaceNote (Maybe Text)
mnNoteId = lens _mnNoteId (\ s a -> s{_mnNoteId = a})
mnCreatorRole :: Lens' MarketplaceNote (Maybe Text)
mnCreatorRole
= lens _mnCreatorRole
(\ s a -> s{_mnCreatorRole = a})
instance FromJSON MarketplaceNote where
parseJSON
= withObject "MarketplaceNote"
(\ o ->
MarketplaceNote' <$>
(o .:? "note") <*>
(o .:? "kind" .!= "adexchangebuyer#marketplaceNote")
<*> (o .:? "timestampMs")
<*> (o .:? "proposalId")
<*> (o .:? "dealId")
<*> (o .:? "proposalRevisionNumber")
<*> (o .:? "noteId")
<*> (o .:? "creatorRole"))
instance ToJSON MarketplaceNote where
toJSON MarketplaceNote'{..}
= object
(catMaybes
[("note" .=) <$> _mnNote, Just ("kind" .= _mnKind),
("timestampMs" .=) <$> _mnTimestampMs,
("proposalId" .=) <$> _mnProposalId,
("dealId" .=) <$> _mnDealId,
("proposalRevisionNumber" .=) <$>
_mnProposalRevisionNumber,
("noteId" .=) <$> _mnNoteId,
("creatorRole" .=) <$> _mnCreatorRole])
data CreativeNATiveAd = CreativeNATiveAd'
{ _cnataImage :: !(Maybe CreativeNATiveAdImage)
, _cnataAppIcon :: !(Maybe CreativeNATiveAdAppIcon)
, _cnataClickTrackingURL :: !(Maybe Text)
, _cnataClickLinkURL :: !(Maybe Text)
, _cnataBody :: !(Maybe Text)
, _cnataHeadline :: !(Maybe Text)
, _cnataImpressionTrackingURL :: !(Maybe [Text])
, _cnataCallToAction :: !(Maybe Text)
, _cnataStore :: !(Maybe Text)
, _cnataVideoURL :: !(Maybe Text)
, _cnataPrice :: !(Maybe Text)
, _cnataAdvertiser :: !(Maybe Text)
, _cnataStarRating :: !(Maybe (Textual Double))
, _cnataLogo :: !(Maybe CreativeNATiveAdLogo)
} deriving (Eq,Show,Data,Typeable,Generic)
creativeNATiveAd
:: CreativeNATiveAd
creativeNATiveAd =
CreativeNATiveAd'
{ _cnataImage = Nothing
, _cnataAppIcon = Nothing
, _cnataClickTrackingURL = Nothing
, _cnataClickLinkURL = Nothing
, _cnataBody = Nothing
, _cnataHeadline = Nothing
, _cnataImpressionTrackingURL = Nothing
, _cnataCallToAction = Nothing
, _cnataStore = Nothing
, _cnataVideoURL = Nothing
, _cnataPrice = Nothing
, _cnataAdvertiser = Nothing
, _cnataStarRating = Nothing
, _cnataLogo = Nothing
}
cnataImage :: Lens' CreativeNATiveAd (Maybe CreativeNATiveAdImage)
cnataImage
= lens _cnataImage (\ s a -> s{_cnataImage = a})
cnataAppIcon :: Lens' CreativeNATiveAd (Maybe CreativeNATiveAdAppIcon)
cnataAppIcon
= lens _cnataAppIcon (\ s a -> s{_cnataAppIcon = a})
cnataClickTrackingURL :: Lens' CreativeNATiveAd (Maybe Text)
cnataClickTrackingURL
= lens _cnataClickTrackingURL
(\ s a -> s{_cnataClickTrackingURL = a})
cnataClickLinkURL :: Lens' CreativeNATiveAd (Maybe Text)
cnataClickLinkURL
= lens _cnataClickLinkURL
(\ s a -> s{_cnataClickLinkURL = a})
cnataBody :: Lens' CreativeNATiveAd (Maybe Text)
cnataBody
= lens _cnataBody (\ s a -> s{_cnataBody = a})
cnataHeadline :: Lens' CreativeNATiveAd (Maybe Text)
cnataHeadline
= lens _cnataHeadline
(\ s a -> s{_cnataHeadline = a})
cnataImpressionTrackingURL :: Lens' CreativeNATiveAd [Text]
cnataImpressionTrackingURL
= lens _cnataImpressionTrackingURL
(\ s a -> s{_cnataImpressionTrackingURL = a})
. _Default
. _Coerce
cnataCallToAction :: Lens' CreativeNATiveAd (Maybe Text)
cnataCallToAction
= lens _cnataCallToAction
(\ s a -> s{_cnataCallToAction = a})
cnataStore :: Lens' CreativeNATiveAd (Maybe Text)
cnataStore
= lens _cnataStore (\ s a -> s{_cnataStore = a})
cnataVideoURL :: Lens' CreativeNATiveAd (Maybe Text)
cnataVideoURL
= lens _cnataVideoURL
(\ s a -> s{_cnataVideoURL = a})
cnataPrice :: Lens' CreativeNATiveAd (Maybe Text)
cnataPrice
= lens _cnataPrice (\ s a -> s{_cnataPrice = a})
cnataAdvertiser :: Lens' CreativeNATiveAd (Maybe Text)
cnataAdvertiser
= lens _cnataAdvertiser
(\ s a -> s{_cnataAdvertiser = a})
cnataStarRating :: Lens' CreativeNATiveAd (Maybe Double)
cnataStarRating
= lens _cnataStarRating
(\ s a -> s{_cnataStarRating = a})
. mapping _Coerce
cnataLogo :: Lens' CreativeNATiveAd (Maybe CreativeNATiveAdLogo)
cnataLogo
= lens _cnataLogo (\ s a -> s{_cnataLogo = a})
instance FromJSON CreativeNATiveAd where
parseJSON
= withObject "CreativeNATiveAd"
(\ o ->
CreativeNATiveAd' <$>
(o .:? "image") <*> (o .:? "appIcon") <*>
(o .:? "clickTrackingUrl")
<*> (o .:? "clickLinkUrl")
<*> (o .:? "body")
<*> (o .:? "headline")
<*> (o .:? "impressionTrackingUrl" .!= mempty)
<*> (o .:? "callToAction")
<*> (o .:? "store")
<*> (o .:? "videoURL")
<*> (o .:? "price")
<*> (o .:? "advertiser")
<*> (o .:? "starRating")
<*> (o .:? "logo"))
instance ToJSON CreativeNATiveAd where
toJSON CreativeNATiveAd'{..}
= object
(catMaybes
[("image" .=) <$> _cnataImage,
("appIcon" .=) <$> _cnataAppIcon,
("clickTrackingUrl" .=) <$> _cnataClickTrackingURL,
("clickLinkUrl" .=) <$> _cnataClickLinkURL,
("body" .=) <$> _cnataBody,
("headline" .=) <$> _cnataHeadline,
("impressionTrackingUrl" .=) <$>
_cnataImpressionTrackingURL,
("callToAction" .=) <$> _cnataCallToAction,
("store" .=) <$> _cnataStore,
("videoURL" .=) <$> _cnataVideoURL,
("price" .=) <$> _cnataPrice,
("advertiser" .=) <$> _cnataAdvertiser,
("starRating" .=) <$> _cnataStarRating,
("logo" .=) <$> _cnataLogo])
data EditAllOrderDealsResponse = EditAllOrderDealsResponse'
{ _eaodrDeals :: !(Maybe [MarketplaceDeal])
, _eaodrOrderRevisionNumber :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
editAllOrderDealsResponse
:: EditAllOrderDealsResponse
editAllOrderDealsResponse =
EditAllOrderDealsResponse'
{ _eaodrDeals = Nothing
, _eaodrOrderRevisionNumber = Nothing
}
eaodrDeals :: Lens' EditAllOrderDealsResponse [MarketplaceDeal]
eaodrDeals
= lens _eaodrDeals (\ s a -> s{_eaodrDeals = a}) .
_Default
. _Coerce
eaodrOrderRevisionNumber :: Lens' EditAllOrderDealsResponse (Maybe Int64)
eaodrOrderRevisionNumber
= lens _eaodrOrderRevisionNumber
(\ s a -> s{_eaodrOrderRevisionNumber = a})
. mapping _Coerce
instance FromJSON EditAllOrderDealsResponse where
parseJSON
= withObject "EditAllOrderDealsResponse"
(\ o ->
EditAllOrderDealsResponse' <$>
(o .:? "deals" .!= mempty) <*>
(o .:? "orderRevisionNumber"))
instance ToJSON EditAllOrderDealsResponse where
toJSON EditAllOrderDealsResponse'{..}
= object
(catMaybes
[("deals" .=) <$> _eaodrDeals,
("orderRevisionNumber" .=) <$>
_eaodrOrderRevisionNumber])
data CreativesList = CreativesList'
{ _clNextPageToken :: !(Maybe Text)
, _clKind :: !Text
, _clItems :: !(Maybe [Creative])
} deriving (Eq,Show,Data,Typeable,Generic)
creativesList
:: CreativesList
creativesList =
CreativesList'
{ _clNextPageToken = Nothing
, _clKind = "adexchangebuyer#creativesList"
, _clItems = Nothing
}
clNextPageToken :: Lens' CreativesList (Maybe Text)
clNextPageToken
= lens _clNextPageToken
(\ s a -> s{_clNextPageToken = a})
clKind :: Lens' CreativesList Text
clKind = lens _clKind (\ s a -> s{_clKind = a})
clItems :: Lens' CreativesList [Creative]
clItems
= lens _clItems (\ s a -> s{_clItems = a}) . _Default
. _Coerce
instance FromJSON CreativesList where
parseJSON
= withObject "CreativesList"
(\ o ->
CreativesList' <$>
(o .:? "nextPageToken") <*>
(o .:? "kind" .!= "adexchangebuyer#creativesList")
<*> (o .:? "items" .!= mempty))
instance ToJSON CreativesList where
toJSON CreativesList'{..}
= object
(catMaybes
[("nextPageToken" .=) <$> _clNextPageToken,
Just ("kind" .= _clKind), ("items" .=) <$> _clItems])
data CreativeDealIdsDealStatusesItem = CreativeDealIdsDealStatusesItem'
{ _cdidsiArcStatus :: !(Maybe Text)
, _cdidsiWebPropertyId :: !(Maybe (Textual Int32))
, _cdidsiDealId :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
creativeDealIdsDealStatusesItem
:: CreativeDealIdsDealStatusesItem
creativeDealIdsDealStatusesItem =
CreativeDealIdsDealStatusesItem'
{ _cdidsiArcStatus = Nothing
, _cdidsiWebPropertyId = Nothing
, _cdidsiDealId = Nothing
}
cdidsiArcStatus :: Lens' CreativeDealIdsDealStatusesItem (Maybe Text)
cdidsiArcStatus
= lens _cdidsiArcStatus
(\ s a -> s{_cdidsiArcStatus = a})
cdidsiWebPropertyId :: Lens' CreativeDealIdsDealStatusesItem (Maybe Int32)
cdidsiWebPropertyId
= lens _cdidsiWebPropertyId
(\ s a -> s{_cdidsiWebPropertyId = a})
. mapping _Coerce
cdidsiDealId :: Lens' CreativeDealIdsDealStatusesItem (Maybe Int64)
cdidsiDealId
= lens _cdidsiDealId (\ s a -> s{_cdidsiDealId = a})
. mapping _Coerce
instance FromJSON CreativeDealIdsDealStatusesItem
where
parseJSON
= withObject "CreativeDealIdsDealStatusesItem"
(\ o ->
CreativeDealIdsDealStatusesItem' <$>
(o .:? "arcStatus") <*> (o .:? "webPropertyId") <*>
(o .:? "dealId"))
instance ToJSON CreativeDealIdsDealStatusesItem where
toJSON CreativeDealIdsDealStatusesItem'{..}
= object
(catMaybes
[("arcStatus" .=) <$> _cdidsiArcStatus,
("webPropertyId" .=) <$> _cdidsiWebPropertyId,
("dealId" .=) <$> _cdidsiDealId])
data CreativeServingRestrictionsItemContextsItem = CreativeServingRestrictionsItemContextsItem'
{ _csriciPlatform :: !(Maybe [Text])
, _csriciContextType :: !(Maybe Text)
, _csriciAuctionType :: !(Maybe [Text])
, _csriciGeoCriteriaId :: !(Maybe [Textual Int32])
} deriving (Eq,Show,Data,Typeable,Generic)
creativeServingRestrictionsItemContextsItem
:: CreativeServingRestrictionsItemContextsItem
creativeServingRestrictionsItemContextsItem =
CreativeServingRestrictionsItemContextsItem'
{ _csriciPlatform = Nothing
, _csriciContextType = Nothing
, _csriciAuctionType = Nothing
, _csriciGeoCriteriaId = Nothing
}
csriciPlatform :: Lens' CreativeServingRestrictionsItemContextsItem [Text]
csriciPlatform
= lens _csriciPlatform
(\ s a -> s{_csriciPlatform = a})
. _Default
. _Coerce
csriciContextType :: Lens' CreativeServingRestrictionsItemContextsItem (Maybe Text)
csriciContextType
= lens _csriciContextType
(\ s a -> s{_csriciContextType = a})
csriciAuctionType :: Lens' CreativeServingRestrictionsItemContextsItem [Text]
csriciAuctionType
= lens _csriciAuctionType
(\ s a -> s{_csriciAuctionType = a})
. _Default
. _Coerce
csriciGeoCriteriaId :: Lens' CreativeServingRestrictionsItemContextsItem [Int32]
csriciGeoCriteriaId
= lens _csriciGeoCriteriaId
(\ s a -> s{_csriciGeoCriteriaId = a})
. _Default
. _Coerce
instance FromJSON
CreativeServingRestrictionsItemContextsItem where
parseJSON
= withObject
"CreativeServingRestrictionsItemContextsItem"
(\ o ->
CreativeServingRestrictionsItemContextsItem' <$>
(o .:? "platform" .!= mempty) <*>
(o .:? "contextType")
<*> (o .:? "auctionType" .!= mempty)
<*> (o .:? "geoCriteriaId" .!= mempty))
instance ToJSON
CreativeServingRestrictionsItemContextsItem where
toJSON
CreativeServingRestrictionsItemContextsItem'{..}
= object
(catMaybes
[("platform" .=) <$> _csriciPlatform,
("contextType" .=) <$> _csriciContextType,
("auctionType" .=) <$> _csriciAuctionType,
("geoCriteriaId" .=) <$> _csriciGeoCriteriaId])
newtype CreateOrdersResponse = CreateOrdersResponse'
{ _corProposals :: Maybe [Proposal]
} deriving (Eq,Show,Data,Typeable,Generic)
createOrdersResponse
:: CreateOrdersResponse
createOrdersResponse =
CreateOrdersResponse'
{ _corProposals = Nothing
}
corProposals :: Lens' CreateOrdersResponse [Proposal]
corProposals
= lens _corProposals (\ s a -> s{_corProposals = a})
. _Default
. _Coerce
instance FromJSON CreateOrdersResponse where
parseJSON
= withObject "CreateOrdersResponse"
(\ o ->
CreateOrdersResponse' <$>
(o .:? "proposals" .!= mempty))
instance ToJSON CreateOrdersResponse where
toJSON CreateOrdersResponse'{..}
= object
(catMaybes [("proposals" .=) <$> _corProposals])
data AccountBidderLocationItem = AccountBidderLocationItem'
{ _abliURL :: !(Maybe Text)
, _abliMaximumQps :: !(Maybe (Textual Int32))
, _abliRegion :: !(Maybe Text)
, _abliBidProtocol :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
accountBidderLocationItem
:: AccountBidderLocationItem
accountBidderLocationItem =
AccountBidderLocationItem'
{ _abliURL = Nothing
, _abliMaximumQps = Nothing
, _abliRegion = Nothing
, _abliBidProtocol = Nothing
}
abliURL :: Lens' AccountBidderLocationItem (Maybe Text)
abliURL = lens _abliURL (\ s a -> s{_abliURL = a})
abliMaximumQps :: Lens' AccountBidderLocationItem (Maybe Int32)
abliMaximumQps
= lens _abliMaximumQps
(\ s a -> s{_abliMaximumQps = a})
. mapping _Coerce
abliRegion :: Lens' AccountBidderLocationItem (Maybe Text)
abliRegion
= lens _abliRegion (\ s a -> s{_abliRegion = a})
abliBidProtocol :: Lens' AccountBidderLocationItem (Maybe Text)
abliBidProtocol
= lens _abliBidProtocol
(\ s a -> s{_abliBidProtocol = a})
instance FromJSON AccountBidderLocationItem where
parseJSON
= withObject "AccountBidderLocationItem"
(\ o ->
AccountBidderLocationItem' <$>
(o .:? "url") <*> (o .:? "maximumQps") <*>
(o .:? "region")
<*> (o .:? "bidProtocol"))
instance ToJSON AccountBidderLocationItem where
toJSON AccountBidderLocationItem'{..}
= object
(catMaybes
[("url" .=) <$> _abliURL,
("maximumQps" .=) <$> _abliMaximumQps,
("region" .=) <$> _abliRegion,
("bidProtocol" .=) <$> _abliBidProtocol])
data PrivateData = PrivateData'
{ _pdReferencePayload :: !(Maybe Bytes)
, _pdReferenceId :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
privateData
:: PrivateData
privateData =
PrivateData'
{ _pdReferencePayload = Nothing
, _pdReferenceId = Nothing
}
pdReferencePayload :: Lens' PrivateData (Maybe ByteString)
pdReferencePayload
= lens _pdReferencePayload
(\ s a -> s{_pdReferencePayload = a})
. mapping _Bytes
pdReferenceId :: Lens' PrivateData (Maybe Text)
pdReferenceId
= lens _pdReferenceId
(\ s a -> s{_pdReferenceId = a})
instance FromJSON PrivateData where
parseJSON
= withObject "PrivateData"
(\ o ->
PrivateData' <$>
(o .:? "referencePayload") <*> (o .:? "referenceId"))
instance ToJSON PrivateData where
toJSON PrivateData'{..}
= object
(catMaybes
[("referencePayload" .=) <$> _pdReferencePayload,
("referenceId" .=) <$> _pdReferenceId])
data Budget = Budget'
{ _bCurrencyCode :: !(Maybe Text)
, _bKind :: !Text
, _bBudgetAmount :: !(Maybe (Textual Int64))
, _bAccountId :: !(Maybe (Textual Int64))
, _bId :: !(Maybe Text)
, _bBillingId :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
budget
:: Budget
budget =
Budget'
{ _bCurrencyCode = Nothing
, _bKind = "adexchangebuyer#budget"
, _bBudgetAmount = Nothing
, _bAccountId = Nothing
, _bId = Nothing
, _bBillingId = Nothing
}
bCurrencyCode :: Lens' Budget (Maybe Text)
bCurrencyCode
= lens _bCurrencyCode
(\ s a -> s{_bCurrencyCode = a})
bKind :: Lens' Budget Text
bKind = lens _bKind (\ s a -> s{_bKind = a})
bBudgetAmount :: Lens' Budget (Maybe Int64)
bBudgetAmount
= lens _bBudgetAmount
(\ s a -> s{_bBudgetAmount = a})
. mapping _Coerce
bAccountId :: Lens' Budget (Maybe Int64)
bAccountId
= lens _bAccountId (\ s a -> s{_bAccountId = a}) .
mapping _Coerce
bId :: Lens' Budget (Maybe Text)
bId = lens _bId (\ s a -> s{_bId = a})
bBillingId :: Lens' Budget (Maybe Int64)
bBillingId
= lens _bBillingId (\ s a -> s{_bBillingId = a}) .
mapping _Coerce
instance FromJSON Budget where
parseJSON
= withObject "Budget"
(\ o ->
Budget' <$>
(o .:? "currencyCode") <*>
(o .:? "kind" .!= "adexchangebuyer#budget")
<*> (o .:? "budgetAmount")
<*> (o .:? "accountId")
<*> (o .:? "id")
<*> (o .:? "billingId"))
instance ToJSON Budget where
toJSON Budget'{..}
= object
(catMaybes
[("currencyCode" .=) <$> _bCurrencyCode,
Just ("kind" .= _bKind),
("budgetAmount" .=) <$> _bBudgetAmount,
("accountId" .=) <$> _bAccountId, ("id" .=) <$> _bId,
("billingId" .=) <$> _bBillingId])
newtype AddOrderNotesRequest = AddOrderNotesRequest'
{ _aonrNotes :: Maybe [MarketplaceNote]
} deriving (Eq,Show,Data,Typeable,Generic)
addOrderNotesRequest
:: AddOrderNotesRequest
addOrderNotesRequest =
AddOrderNotesRequest'
{ _aonrNotes = Nothing
}
aonrNotes :: Lens' AddOrderNotesRequest [MarketplaceNote]
aonrNotes
= lens _aonrNotes (\ s a -> s{_aonrNotes = a}) .
_Default
. _Coerce
instance FromJSON AddOrderNotesRequest where
parseJSON
= withObject "AddOrderNotesRequest"
(\ o ->
AddOrderNotesRequest' <$> (o .:? "notes" .!= mempty))
instance ToJSON AddOrderNotesRequest where
toJSON AddOrderNotesRequest'{..}
= object (catMaybes [("notes" .=) <$> _aonrNotes])
data DeliveryControlFrequencyCap = DeliveryControlFrequencyCap'
{ _dcfcMaxImpressions :: !(Maybe (Textual Int32))
, _dcfcNumTimeUnits :: !(Maybe (Textual Int32))
, _dcfcTimeUnitType :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
deliveryControlFrequencyCap
:: DeliveryControlFrequencyCap
deliveryControlFrequencyCap =
DeliveryControlFrequencyCap'
{ _dcfcMaxImpressions = Nothing
, _dcfcNumTimeUnits = Nothing
, _dcfcTimeUnitType = Nothing
}
dcfcMaxImpressions :: Lens' DeliveryControlFrequencyCap (Maybe Int32)
dcfcMaxImpressions
= lens _dcfcMaxImpressions
(\ s a -> s{_dcfcMaxImpressions = a})
. mapping _Coerce
dcfcNumTimeUnits :: Lens' DeliveryControlFrequencyCap (Maybe Int32)
dcfcNumTimeUnits
= lens _dcfcNumTimeUnits
(\ s a -> s{_dcfcNumTimeUnits = a})
. mapping _Coerce
dcfcTimeUnitType :: Lens' DeliveryControlFrequencyCap (Maybe Text)
dcfcTimeUnitType
= lens _dcfcTimeUnitType
(\ s a -> s{_dcfcTimeUnitType = a})
instance FromJSON DeliveryControlFrequencyCap where
parseJSON
= withObject "DeliveryControlFrequencyCap"
(\ o ->
DeliveryControlFrequencyCap' <$>
(o .:? "maxImpressions") <*> (o .:? "numTimeUnits")
<*> (o .:? "timeUnitType"))
instance ToJSON DeliveryControlFrequencyCap where
toJSON DeliveryControlFrequencyCap'{..}
= object
(catMaybes
[("maxImpressions" .=) <$> _dcfcMaxImpressions,
("numTimeUnits" .=) <$> _dcfcNumTimeUnits,
("timeUnitType" .=) <$> _dcfcTimeUnitType])
data MarketplaceDealParty = MarketplaceDealParty'
{ _mdpSeller :: !(Maybe Seller)
, _mdpBuyer :: !(Maybe Buyer)
} deriving (Eq,Show,Data,Typeable,Generic)
marketplaceDealParty
:: MarketplaceDealParty
marketplaceDealParty =
MarketplaceDealParty'
{ _mdpSeller = Nothing
, _mdpBuyer = Nothing
}
mdpSeller :: Lens' MarketplaceDealParty (Maybe Seller)
mdpSeller
= lens _mdpSeller (\ s a -> s{_mdpSeller = a})
mdpBuyer :: Lens' MarketplaceDealParty (Maybe Buyer)
mdpBuyer = lens _mdpBuyer (\ s a -> s{_mdpBuyer = a})
instance FromJSON MarketplaceDealParty where
parseJSON
= withObject "MarketplaceDealParty"
(\ o ->
MarketplaceDealParty' <$>
(o .:? "seller") <*> (o .:? "buyer"))
instance ToJSON MarketplaceDealParty where
toJSON MarketplaceDealParty'{..}
= object
(catMaybes
[("seller" .=) <$> _mdpSeller,
("buyer" .=) <$> _mdpBuyer])
newtype GetOrderNotesResponse = GetOrderNotesResponse'
{ _gonrNotes :: Maybe [MarketplaceNote]
} deriving (Eq,Show,Data,Typeable,Generic)
getOrderNotesResponse
:: GetOrderNotesResponse
getOrderNotesResponse =
GetOrderNotesResponse'
{ _gonrNotes = Nothing
}
gonrNotes :: Lens' GetOrderNotesResponse [MarketplaceNote]
gonrNotes
= lens _gonrNotes (\ s a -> s{_gonrNotes = a}) .
_Default
. _Coerce
instance FromJSON GetOrderNotesResponse where
parseJSON
= withObject "GetOrderNotesResponse"
(\ o ->
GetOrderNotesResponse' <$>
(o .:? "notes" .!= mempty))
instance ToJSON GetOrderNotesResponse where
toJSON GetOrderNotesResponse'{..}
= object (catMaybes [("notes" .=) <$> _gonrNotes])
newtype GetOrdersResponse = GetOrdersResponse'
{ _gorProposals :: Maybe [Proposal]
} deriving (Eq,Show,Data,Typeable,Generic)
getOrdersResponse
:: GetOrdersResponse
getOrdersResponse =
GetOrdersResponse'
{ _gorProposals = Nothing
}
gorProposals :: Lens' GetOrdersResponse [Proposal]
gorProposals
= lens _gorProposals (\ s a -> s{_gorProposals = a})
. _Default
. _Coerce
instance FromJSON GetOrdersResponse where
parseJSON
= withObject "GetOrdersResponse"
(\ o ->
GetOrdersResponse' <$>
(o .:? "proposals" .!= mempty))
instance ToJSON GetOrdersResponse where
toJSON GetOrdersResponse'{..}
= object
(catMaybes [("proposals" .=) <$> _gorProposals])
data CreativeServingRestrictionsItemDisApprovalReasonsItem = CreativeServingRestrictionsItemDisApprovalReasonsItem'
{ _csridariReason :: !(Maybe Text)
, _csridariDetails :: !(Maybe [Text])
} deriving (Eq,Show,Data,Typeable,Generic)
creativeServingRestrictionsItemDisApprovalReasonsItem
:: CreativeServingRestrictionsItemDisApprovalReasonsItem
creativeServingRestrictionsItemDisApprovalReasonsItem =
CreativeServingRestrictionsItemDisApprovalReasonsItem'
{ _csridariReason = Nothing
, _csridariDetails = Nothing
}
csridariReason :: Lens' CreativeServingRestrictionsItemDisApprovalReasonsItem (Maybe Text)
csridariReason
= lens _csridariReason
(\ s a -> s{_csridariReason = a})
csridariDetails :: Lens' CreativeServingRestrictionsItemDisApprovalReasonsItem [Text]
csridariDetails
= lens _csridariDetails
(\ s a -> s{_csridariDetails = a})
. _Default
. _Coerce
instance FromJSON
CreativeServingRestrictionsItemDisApprovalReasonsItem
where
parseJSON
= withObject
"CreativeServingRestrictionsItemDisApprovalReasonsItem"
(\ o ->
CreativeServingRestrictionsItemDisApprovalReasonsItem'
<$>
(o .:? "reason") <*> (o .:? "details" .!= mempty))
instance ToJSON
CreativeServingRestrictionsItemDisApprovalReasonsItem
where
toJSON
CreativeServingRestrictionsItemDisApprovalReasonsItem'{..}
= object
(catMaybes
[("reason" .=) <$> _csridariReason,
("details" .=) <$> _csridariDetails])
data AccountsList = AccountsList'
{ _alKind :: !Text
, _alItems :: !(Maybe [Account])
} deriving (Eq,Show,Data,Typeable,Generic)
accountsList
:: AccountsList
accountsList =
AccountsList'
{ _alKind = "adexchangebuyer#accountsList"
, _alItems = Nothing
}
alKind :: Lens' AccountsList Text
alKind = lens _alKind (\ s a -> s{_alKind = a})
alItems :: Lens' AccountsList [Account]
alItems
= lens _alItems (\ s a -> s{_alItems = a}) . _Default
. _Coerce
instance FromJSON AccountsList where
parseJSON
= withObject "AccountsList"
(\ o ->
AccountsList' <$>
(o .:? "kind" .!= "adexchangebuyer#accountsList") <*>
(o .:? "items" .!= mempty))
instance ToJSON AccountsList where
toJSON AccountsList'{..}
= object
(catMaybes
[Just ("kind" .= _alKind),
("items" .=) <$> _alItems])
data Dimension = Dimension'
{ _dDimensionValues :: !(Maybe [DimensionDimensionValue])
, _dDimensionType :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
dimension
:: Dimension
dimension =
Dimension'
{ _dDimensionValues = Nothing
, _dDimensionType = Nothing
}
dDimensionValues :: Lens' Dimension [DimensionDimensionValue]
dDimensionValues
= lens _dDimensionValues
(\ s a -> s{_dDimensionValues = a})
. _Default
. _Coerce
dDimensionType :: Lens' Dimension (Maybe Text)
dDimensionType
= lens _dDimensionType
(\ s a -> s{_dDimensionType = a})
instance FromJSON Dimension where
parseJSON
= withObject "Dimension"
(\ o ->
Dimension' <$>
(o .:? "dimensionValues" .!= mempty) <*>
(o .:? "dimensionType"))
instance ToJSON Dimension where
toJSON Dimension'{..}
= object
(catMaybes
[("dimensionValues" .=) <$> _dDimensionValues,
("dimensionType" .=) <$> _dDimensionType])
data CreateOrdersRequest = CreateOrdersRequest'
{ _cProposals :: !(Maybe [Proposal])
, _cWebPropertyCode :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
createOrdersRequest
:: CreateOrdersRequest
createOrdersRequest =
CreateOrdersRequest'
{ _cProposals = Nothing
, _cWebPropertyCode = Nothing
}
cProposals :: Lens' CreateOrdersRequest [Proposal]
cProposals
= lens _cProposals (\ s a -> s{_cProposals = a}) .
_Default
. _Coerce
cWebPropertyCode :: Lens' CreateOrdersRequest (Maybe Text)
cWebPropertyCode
= lens _cWebPropertyCode
(\ s a -> s{_cWebPropertyCode = a})
instance FromJSON CreateOrdersRequest where
parseJSON
= withObject "CreateOrdersRequest"
(\ o ->
CreateOrdersRequest' <$>
(o .:? "proposals" .!= mempty) <*>
(o .:? "webPropertyCode"))
instance ToJSON CreateOrdersRequest where
toJSON CreateOrdersRequest'{..}
= object
(catMaybes
[("proposals" .=) <$> _cProposals,
("webPropertyCode" .=) <$> _cWebPropertyCode])
data CreativeCorrectionsItem = CreativeCorrectionsItem'
{ _cciContexts :: !(Maybe [CreativeCorrectionsItemContextsItem])
, _cciReason :: !(Maybe Text)
, _cciDetails :: !(Maybe [Text])
} deriving (Eq,Show,Data,Typeable,Generic)
creativeCorrectionsItem
:: CreativeCorrectionsItem
creativeCorrectionsItem =
CreativeCorrectionsItem'
{ _cciContexts = Nothing
, _cciReason = Nothing
, _cciDetails = Nothing
}
cciContexts :: Lens' CreativeCorrectionsItem [CreativeCorrectionsItemContextsItem]
cciContexts
= lens _cciContexts (\ s a -> s{_cciContexts = a}) .
_Default
. _Coerce
cciReason :: Lens' CreativeCorrectionsItem (Maybe Text)
cciReason
= lens _cciReason (\ s a -> s{_cciReason = a})
cciDetails :: Lens' CreativeCorrectionsItem [Text]
cciDetails
= lens _cciDetails (\ s a -> s{_cciDetails = a}) .
_Default
. _Coerce
instance FromJSON CreativeCorrectionsItem where
parseJSON
= withObject "CreativeCorrectionsItem"
(\ o ->
CreativeCorrectionsItem' <$>
(o .:? "contexts" .!= mempty) <*> (o .:? "reason")
<*> (o .:? "details" .!= mempty))
instance ToJSON CreativeCorrectionsItem where
toJSON CreativeCorrectionsItem'{..}
= object
(catMaybes
[("contexts" .=) <$> _cciContexts,
("reason" .=) <$> _cciReason,
("details" .=) <$> _cciDetails])
data DealTermsRubiconNonGuaranteedTerms = DealTermsRubiconNonGuaranteedTerms'
{ _dtrngtPriorityPrice :: !(Maybe Price)
, _dtrngtStandardPrice :: !(Maybe Price)
} deriving (Eq,Show,Data,Typeable,Generic)
dealTermsRubiconNonGuaranteedTerms
:: DealTermsRubiconNonGuaranteedTerms
dealTermsRubiconNonGuaranteedTerms =
DealTermsRubiconNonGuaranteedTerms'
{ _dtrngtPriorityPrice = Nothing
, _dtrngtStandardPrice = Nothing
}
dtrngtPriorityPrice :: Lens' DealTermsRubiconNonGuaranteedTerms (Maybe Price)
dtrngtPriorityPrice
= lens _dtrngtPriorityPrice
(\ s a -> s{_dtrngtPriorityPrice = a})
dtrngtStandardPrice :: Lens' DealTermsRubiconNonGuaranteedTerms (Maybe Price)
dtrngtStandardPrice
= lens _dtrngtStandardPrice
(\ s a -> s{_dtrngtStandardPrice = a})
instance FromJSON DealTermsRubiconNonGuaranteedTerms
where
parseJSON
= withObject "DealTermsRubiconNonGuaranteedTerms"
(\ o ->
DealTermsRubiconNonGuaranteedTerms' <$>
(o .:? "priorityPrice") <*> (o .:? "standardPrice"))
instance ToJSON DealTermsRubiconNonGuaranteedTerms
where
toJSON DealTermsRubiconNonGuaranteedTerms'{..}
= object
(catMaybes
[("priorityPrice" .=) <$> _dtrngtPriorityPrice,
("standardPrice" .=) <$> _dtrngtStandardPrice])
newtype DealServingMetadata = DealServingMetadata'
{ _dsmDealPauseStatus :: Maybe DealServingMetadataDealPauseStatus
} deriving (Eq,Show,Data,Typeable,Generic)
dealServingMetadata
:: DealServingMetadata
dealServingMetadata =
DealServingMetadata'
{ _dsmDealPauseStatus = Nothing
}
dsmDealPauseStatus :: Lens' DealServingMetadata (Maybe DealServingMetadataDealPauseStatus)
dsmDealPauseStatus
= lens _dsmDealPauseStatus
(\ s a -> s{_dsmDealPauseStatus = a})
instance FromJSON DealServingMetadata where
parseJSON
= withObject "DealServingMetadata"
(\ o ->
DealServingMetadata' <$> (o .:? "dealPauseStatus"))
instance ToJSON DealServingMetadata where
toJSON DealServingMetadata'{..}
= object
(catMaybes
[("dealPauseStatus" .=) <$> _dsmDealPauseStatus])
data AddOrderDealsResponse = AddOrderDealsResponse'
{ _aodrDeals :: !(Maybe [MarketplaceDeal])
, _aodrProposalRevisionNumber :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
addOrderDealsResponse
:: AddOrderDealsResponse
addOrderDealsResponse =
AddOrderDealsResponse'
{ _aodrDeals = Nothing
, _aodrProposalRevisionNumber = Nothing
}
aodrDeals :: Lens' AddOrderDealsResponse [MarketplaceDeal]
aodrDeals
= lens _aodrDeals (\ s a -> s{_aodrDeals = a}) .
_Default
. _Coerce
aodrProposalRevisionNumber :: Lens' AddOrderDealsResponse (Maybe Int64)
aodrProposalRevisionNumber
= lens _aodrProposalRevisionNumber
(\ s a -> s{_aodrProposalRevisionNumber = a})
. mapping _Coerce
instance FromJSON AddOrderDealsResponse where
parseJSON
= withObject "AddOrderDealsResponse"
(\ o ->
AddOrderDealsResponse' <$>
(o .:? "deals" .!= mempty) <*>
(o .:? "proposalRevisionNumber"))
instance ToJSON AddOrderDealsResponse where
toJSON AddOrderDealsResponse'{..}
= object
(catMaybes
[("deals" .=) <$> _aodrDeals,
("proposalRevisionNumber" .=) <$>
_aodrProposalRevisionNumber])
data DeliveryControl = DeliveryControl'
{ _dcCreativeBlockingLevel :: !(Maybe Text)
, _dcFrequencyCaps :: !(Maybe [DeliveryControlFrequencyCap])
, _dcDeliveryRateType :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
deliveryControl
:: DeliveryControl
deliveryControl =
DeliveryControl'
{ _dcCreativeBlockingLevel = Nothing
, _dcFrequencyCaps = Nothing
, _dcDeliveryRateType = Nothing
}
dcCreativeBlockingLevel :: Lens' DeliveryControl (Maybe Text)
dcCreativeBlockingLevel
= lens _dcCreativeBlockingLevel
(\ s a -> s{_dcCreativeBlockingLevel = a})
dcFrequencyCaps :: Lens' DeliveryControl [DeliveryControlFrequencyCap]
dcFrequencyCaps
= lens _dcFrequencyCaps
(\ s a -> s{_dcFrequencyCaps = a})
. _Default
. _Coerce
dcDeliveryRateType :: Lens' DeliveryControl (Maybe Text)
dcDeliveryRateType
= lens _dcDeliveryRateType
(\ s a -> s{_dcDeliveryRateType = a})
instance FromJSON DeliveryControl where
parseJSON
= withObject "DeliveryControl"
(\ o ->
DeliveryControl' <$>
(o .:? "creativeBlockingLevel") <*>
(o .:? "frequencyCaps" .!= mempty)
<*> (o .:? "deliveryRateType"))
instance ToJSON DeliveryControl where
toJSON DeliveryControl'{..}
= object
(catMaybes
[("creativeBlockingLevel" .=) <$>
_dcCreativeBlockingLevel,
("frequencyCaps" .=) <$> _dcFrequencyCaps,
("deliveryRateType" .=) <$> _dcDeliveryRateType])
data PricePerBuyer = PricePerBuyer'
{ _ppbPrice :: !(Maybe Price)
, _ppbAuctionTier :: !(Maybe Text)
, _ppbBuyer :: !(Maybe Buyer)
} deriving (Eq,Show,Data,Typeable,Generic)
pricePerBuyer
:: PricePerBuyer
pricePerBuyer =
PricePerBuyer'
{ _ppbPrice = Nothing
, _ppbAuctionTier = Nothing
, _ppbBuyer = Nothing
}
ppbPrice :: Lens' PricePerBuyer (Maybe Price)
ppbPrice = lens _ppbPrice (\ s a -> s{_ppbPrice = a})
ppbAuctionTier :: Lens' PricePerBuyer (Maybe Text)
ppbAuctionTier
= lens _ppbAuctionTier
(\ s a -> s{_ppbAuctionTier = a})
ppbBuyer :: Lens' PricePerBuyer (Maybe Buyer)
ppbBuyer = lens _ppbBuyer (\ s a -> s{_ppbBuyer = a})
instance FromJSON PricePerBuyer where
parseJSON
= withObject "PricePerBuyer"
(\ o ->
PricePerBuyer' <$>
(o .:? "price") <*> (o .:? "auctionTier") <*>
(o .:? "buyer"))
instance ToJSON PricePerBuyer where
toJSON PricePerBuyer'{..}
= object
(catMaybes
[("price" .=) <$> _ppbPrice,
("auctionTier" .=) <$> _ppbAuctionTier,
("buyer" .=) <$> _ppbBuyer])
data Creative = Creative'
{ _cAttribute :: !(Maybe [Textual Int32])
, _cNATiveAd :: !(Maybe CreativeNATiveAd)
, _cHeight :: !(Maybe (Textual Int32))
, _cBuyerCreativeId :: !(Maybe Text)
, _cAdvertiserName :: !(Maybe Text)
, _cAdChoicesDestinationURL :: !(Maybe Text)
, _cAgencyId :: !(Maybe (Textual Int64))
, _cCorrections :: !(Maybe [CreativeCorrectionsItem])
, _cProductCategories :: !(Maybe [Textual Int32])
, _cKind :: !Text
, _cHTMLSnippet :: !(Maybe Text)
, _cAdvertiserId :: !(Maybe [Textual Int64])
, _cRestrictedCategories :: !(Maybe [Textual Int32])
, _cDealsStatus :: !(Maybe Text)
, _cWidth :: !(Maybe (Textual Int32))
, _cClickThroughURL :: !(Maybe [Text])
, _cLanguages :: !(Maybe [Text])
, _cVendorType :: !(Maybe [Textual Int32])
, _cAccountId :: !(Maybe (Textual Int32))
, _cImpressionTrackingURL :: !(Maybe [Text])
, _cFilteringReasons :: !(Maybe CreativeFilteringReasons)
, _cVersion :: !(Maybe (Textual Int32))
, _cSensitiveCategories :: !(Maybe [Textual Int32])
, _cVideoURL :: !(Maybe Text)
, _cAPIUploadTimestamp :: !(Maybe DateTime')
, _cServingRestrictions :: !(Maybe [CreativeServingRestrictionsItem])
, _cDetectedDomains :: !(Maybe [Text])
, _cOpenAuctionStatus :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
creative
:: Creative
creative =
Creative'
{ _cAttribute = Nothing
, _cNATiveAd = Nothing
, _cHeight = Nothing
, _cBuyerCreativeId = Nothing
, _cAdvertiserName = Nothing
, _cAdChoicesDestinationURL = Nothing
, _cAgencyId = Nothing
, _cCorrections = Nothing
, _cProductCategories = Nothing
, _cKind = "adexchangebuyer#creative"
, _cHTMLSnippet = Nothing
, _cAdvertiserId = Nothing
, _cRestrictedCategories = Nothing
, _cDealsStatus = Nothing
, _cWidth = Nothing
, _cClickThroughURL = Nothing
, _cLanguages = Nothing
, _cVendorType = Nothing
, _cAccountId = Nothing
, _cImpressionTrackingURL = Nothing
, _cFilteringReasons = Nothing
, _cVersion = Nothing
, _cSensitiveCategories = Nothing
, _cVideoURL = Nothing
, _cAPIUploadTimestamp = Nothing
, _cServingRestrictions = Nothing
, _cDetectedDomains = Nothing
, _cOpenAuctionStatus = Nothing
}
cAttribute :: Lens' Creative [Int32]
cAttribute
= lens _cAttribute (\ s a -> s{_cAttribute = a}) .
_Default
. _Coerce
cNATiveAd :: Lens' Creative (Maybe CreativeNATiveAd)
cNATiveAd
= lens _cNATiveAd (\ s a -> s{_cNATiveAd = a})
cHeight :: Lens' Creative (Maybe Int32)
cHeight
= lens _cHeight (\ s a -> s{_cHeight = a}) .
mapping _Coerce
cBuyerCreativeId :: Lens' Creative (Maybe Text)
cBuyerCreativeId
= lens _cBuyerCreativeId
(\ s a -> s{_cBuyerCreativeId = a})
cAdvertiserName :: Lens' Creative (Maybe Text)
cAdvertiserName
= lens _cAdvertiserName
(\ s a -> s{_cAdvertiserName = a})
cAdChoicesDestinationURL :: Lens' Creative (Maybe Text)
cAdChoicesDestinationURL
= lens _cAdChoicesDestinationURL
(\ s a -> s{_cAdChoicesDestinationURL = a})
cAgencyId :: Lens' Creative (Maybe Int64)
cAgencyId
= lens _cAgencyId (\ s a -> s{_cAgencyId = a}) .
mapping _Coerce
cCorrections :: Lens' Creative [CreativeCorrectionsItem]
cCorrections
= lens _cCorrections (\ s a -> s{_cCorrections = a})
. _Default
. _Coerce
cProductCategories :: Lens' Creative [Int32]
cProductCategories
= lens _cProductCategories
(\ s a -> s{_cProductCategories = a})
. _Default
. _Coerce
cKind :: Lens' Creative Text
cKind = lens _cKind (\ s a -> s{_cKind = a})
cHTMLSnippet :: Lens' Creative (Maybe Text)
cHTMLSnippet
= lens _cHTMLSnippet (\ s a -> s{_cHTMLSnippet = a})
cAdvertiserId :: Lens' Creative [Int64]
cAdvertiserId
= lens _cAdvertiserId
(\ s a -> s{_cAdvertiserId = a})
. _Default
. _Coerce
cRestrictedCategories :: Lens' Creative [Int32]
cRestrictedCategories
= lens _cRestrictedCategories
(\ s a -> s{_cRestrictedCategories = a})
. _Default
. _Coerce
cDealsStatus :: Lens' Creative (Maybe Text)
cDealsStatus
= lens _cDealsStatus (\ s a -> s{_cDealsStatus = a})
cWidth :: Lens' Creative (Maybe Int32)
cWidth
= lens _cWidth (\ s a -> s{_cWidth = a}) .
mapping _Coerce
cClickThroughURL :: Lens' Creative [Text]
cClickThroughURL
= lens _cClickThroughURL
(\ s a -> s{_cClickThroughURL = a})
. _Default
. _Coerce
cLanguages :: Lens' Creative [Text]
cLanguages
= lens _cLanguages (\ s a -> s{_cLanguages = a}) .
_Default
. _Coerce
cVendorType :: Lens' Creative [Int32]
cVendorType
= lens _cVendorType (\ s a -> s{_cVendorType = a}) .
_Default
. _Coerce
cAccountId :: Lens' Creative (Maybe Int32)
cAccountId
= lens _cAccountId (\ s a -> s{_cAccountId = a}) .
mapping _Coerce
cImpressionTrackingURL :: Lens' Creative [Text]
cImpressionTrackingURL
= lens _cImpressionTrackingURL
(\ s a -> s{_cImpressionTrackingURL = a})
. _Default
. _Coerce
cFilteringReasons :: Lens' Creative (Maybe CreativeFilteringReasons)
cFilteringReasons
= lens _cFilteringReasons
(\ s a -> s{_cFilteringReasons = a})
cVersion :: Lens' Creative (Maybe Int32)
cVersion
= lens _cVersion (\ s a -> s{_cVersion = a}) .
mapping _Coerce
cSensitiveCategories :: Lens' Creative [Int32]
cSensitiveCategories
= lens _cSensitiveCategories
(\ s a -> s{_cSensitiveCategories = a})
. _Default
. _Coerce
cVideoURL :: Lens' Creative (Maybe Text)
cVideoURL
= lens _cVideoURL (\ s a -> s{_cVideoURL = a})
cAPIUploadTimestamp :: Lens' Creative (Maybe UTCTime)
cAPIUploadTimestamp
= lens _cAPIUploadTimestamp
(\ s a -> s{_cAPIUploadTimestamp = a})
. mapping _DateTime
cServingRestrictions :: Lens' Creative [CreativeServingRestrictionsItem]
cServingRestrictions
= lens _cServingRestrictions
(\ s a -> s{_cServingRestrictions = a})
. _Default
. _Coerce
cDetectedDomains :: Lens' Creative [Text]
cDetectedDomains
= lens _cDetectedDomains
(\ s a -> s{_cDetectedDomains = a})
. _Default
. _Coerce
cOpenAuctionStatus :: Lens' Creative (Maybe Text)
cOpenAuctionStatus
= lens _cOpenAuctionStatus
(\ s a -> s{_cOpenAuctionStatus = a})
instance FromJSON Creative where
parseJSON
= withObject "Creative"
(\ o ->
Creative' <$>
(o .:? "attribute" .!= mempty) <*> (o .:? "nativeAd")
<*> (o .:? "height")
<*> (o .:? "buyerCreativeId")
<*> (o .:? "advertiserName")
<*> (o .:? "adChoicesDestinationUrl")
<*> (o .:? "agencyId")
<*> (o .:? "corrections" .!= mempty)
<*> (o .:? "productCategories" .!= mempty)
<*> (o .:? "kind" .!= "adexchangebuyer#creative")
<*> (o .:? "HTMLSnippet")
<*> (o .:? "advertiserId" .!= mempty)
<*> (o .:? "restrictedCategories" .!= mempty)
<*> (o .:? "dealsStatus")
<*> (o .:? "width")
<*> (o .:? "clickThroughUrl" .!= mempty)
<*> (o .:? "languages" .!= mempty)
<*> (o .:? "vendorType" .!= mempty)
<*> (o .:? "accountId")
<*> (o .:? "impressionTrackingUrl" .!= mempty)
<*> (o .:? "filteringReasons")
<*> (o .:? "version")
<*> (o .:? "sensitiveCategories" .!= mempty)
<*> (o .:? "videoURL")
<*> (o .:? "apiUploadTimestamp")
<*> (o .:? "servingRestrictions" .!= mempty)
<*> (o .:? "detectedDomains" .!= mempty)
<*> (o .:? "openAuctionStatus"))
instance ToJSON Creative where
toJSON Creative'{..}
= object
(catMaybes
[("attribute" .=) <$> _cAttribute,
("nativeAd" .=) <$> _cNATiveAd,
("height" .=) <$> _cHeight,
("buyerCreativeId" .=) <$> _cBuyerCreativeId,
("advertiserName" .=) <$> _cAdvertiserName,
("adChoicesDestinationUrl" .=) <$>
_cAdChoicesDestinationURL,
("agencyId" .=) <$> _cAgencyId,
("corrections" .=) <$> _cCorrections,
("productCategories" .=) <$> _cProductCategories,
Just ("kind" .= _cKind),
("HTMLSnippet" .=) <$> _cHTMLSnippet,
("advertiserId" .=) <$> _cAdvertiserId,
("restrictedCategories" .=) <$>
_cRestrictedCategories,
("dealsStatus" .=) <$> _cDealsStatus,
("width" .=) <$> _cWidth,
("clickThroughUrl" .=) <$> _cClickThroughURL,
("languages" .=) <$> _cLanguages,
("vendorType" .=) <$> _cVendorType,
("accountId" .=) <$> _cAccountId,
("impressionTrackingUrl" .=) <$>
_cImpressionTrackingURL,
("filteringReasons" .=) <$> _cFilteringReasons,
("version" .=) <$> _cVersion,
("sensitiveCategories" .=) <$> _cSensitiveCategories,
("videoURL" .=) <$> _cVideoURL,
("apiUploadTimestamp" .=) <$> _cAPIUploadTimestamp,
("servingRestrictions" .=) <$> _cServingRestrictions,
("detectedDomains" .=) <$> _cDetectedDomains,
("openAuctionStatus" .=) <$> _cOpenAuctionStatus])
data TargetingValueDayPartTargetingDayPart = TargetingValueDayPartTargetingDayPart'
{ _tvdptdpEndHour :: !(Maybe (Textual Int32))
, _tvdptdpStartHour :: !(Maybe (Textual Int32))
, _tvdptdpStartMinute :: !(Maybe (Textual Int32))
, _tvdptdpDayOfWeek :: !(Maybe Text)
, _tvdptdpEndMinute :: !(Maybe (Textual Int32))
} deriving (Eq,Show,Data,Typeable,Generic)
targetingValueDayPartTargetingDayPart
:: TargetingValueDayPartTargetingDayPart
targetingValueDayPartTargetingDayPart =
TargetingValueDayPartTargetingDayPart'
{ _tvdptdpEndHour = Nothing
, _tvdptdpStartHour = Nothing
, _tvdptdpStartMinute = Nothing
, _tvdptdpDayOfWeek = Nothing
, _tvdptdpEndMinute = Nothing
}
tvdptdpEndHour :: Lens' TargetingValueDayPartTargetingDayPart (Maybe Int32)
tvdptdpEndHour
= lens _tvdptdpEndHour
(\ s a -> s{_tvdptdpEndHour = a})
. mapping _Coerce
tvdptdpStartHour :: Lens' TargetingValueDayPartTargetingDayPart (Maybe Int32)
tvdptdpStartHour
= lens _tvdptdpStartHour
(\ s a -> s{_tvdptdpStartHour = a})
. mapping _Coerce
tvdptdpStartMinute :: Lens' TargetingValueDayPartTargetingDayPart (Maybe Int32)
tvdptdpStartMinute
= lens _tvdptdpStartMinute
(\ s a -> s{_tvdptdpStartMinute = a})
. mapping _Coerce
tvdptdpDayOfWeek :: Lens' TargetingValueDayPartTargetingDayPart (Maybe Text)
tvdptdpDayOfWeek
= lens _tvdptdpDayOfWeek
(\ s a -> s{_tvdptdpDayOfWeek = a})
tvdptdpEndMinute :: Lens' TargetingValueDayPartTargetingDayPart (Maybe Int32)
tvdptdpEndMinute
= lens _tvdptdpEndMinute
(\ s a -> s{_tvdptdpEndMinute = a})
. mapping _Coerce
instance FromJSON
TargetingValueDayPartTargetingDayPart where
parseJSON
= withObject "TargetingValueDayPartTargetingDayPart"
(\ o ->
TargetingValueDayPartTargetingDayPart' <$>
(o .:? "endHour") <*> (o .:? "startHour") <*>
(o .:? "startMinute")
<*> (o .:? "dayOfWeek")
<*> (o .:? "endMinute"))
instance ToJSON TargetingValueDayPartTargetingDayPart
where
toJSON TargetingValueDayPartTargetingDayPart'{..}
= object
(catMaybes
[("endHour" .=) <$> _tvdptdpEndHour,
("startHour" .=) <$> _tvdptdpStartHour,
("startMinute" .=) <$> _tvdptdpStartMinute,
("dayOfWeek" .=) <$> _tvdptdpDayOfWeek,
("endMinute" .=) <$> _tvdptdpEndMinute])
data DimensionDimensionValue = DimensionDimensionValue'
{ _ddvName :: !(Maybe Text)
, _ddvId :: !(Maybe (Textual Int32))
, _ddvPercentage :: !(Maybe (Textual Int32))
} deriving (Eq,Show,Data,Typeable,Generic)
dimensionDimensionValue
:: DimensionDimensionValue
dimensionDimensionValue =
DimensionDimensionValue'
{ _ddvName = Nothing
, _ddvId = Nothing
, _ddvPercentage = Nothing
}
ddvName :: Lens' DimensionDimensionValue (Maybe Text)
ddvName = lens _ddvName (\ s a -> s{_ddvName = a})
ddvId :: Lens' DimensionDimensionValue (Maybe Int32)
ddvId
= lens _ddvId (\ s a -> s{_ddvId = a}) .
mapping _Coerce
ddvPercentage :: Lens' DimensionDimensionValue (Maybe Int32)
ddvPercentage
= lens _ddvPercentage
(\ s a -> s{_ddvPercentage = a})
. mapping _Coerce
instance FromJSON DimensionDimensionValue where
parseJSON
= withObject "DimensionDimensionValue"
(\ o ->
DimensionDimensionValue' <$>
(o .:? "name") <*> (o .:? "id") <*>
(o .:? "percentage"))
instance ToJSON DimensionDimensionValue where
toJSON DimensionDimensionValue'{..}
= object
(catMaybes
[("name" .=) <$> _ddvName, ("id" .=) <$> _ddvId,
("percentage" .=) <$> _ddvPercentage])
data PretargetingConfigList = PretargetingConfigList'
{ _pclKind :: !Text
, _pclItems :: !(Maybe [PretargetingConfig])
} deriving (Eq,Show,Data,Typeable,Generic)
pretargetingConfigList
:: PretargetingConfigList
pretargetingConfigList =
PretargetingConfigList'
{ _pclKind = "adexchangebuyer#pretargetingConfigList"
, _pclItems = Nothing
}
pclKind :: Lens' PretargetingConfigList Text
pclKind = lens _pclKind (\ s a -> s{_pclKind = a})
pclItems :: Lens' PretargetingConfigList [PretargetingConfig]
pclItems
= lens _pclItems (\ s a -> s{_pclItems = a}) .
_Default
. _Coerce
instance FromJSON PretargetingConfigList where
parseJSON
= withObject "PretargetingConfigList"
(\ o ->
PretargetingConfigList' <$>
(o .:? "kind" .!=
"adexchangebuyer#pretargetingConfigList")
<*> (o .:? "items" .!= mempty))
instance ToJSON PretargetingConfigList where
toJSON PretargetingConfigList'{..}
= object
(catMaybes
[Just ("kind" .= _pclKind),
("items" .=) <$> _pclItems])
newtype DealTermsNonGuaranteedFixedPriceTerms = DealTermsNonGuaranteedFixedPriceTerms'
{ _dtngfptFixedPrices :: Maybe [PricePerBuyer]
} deriving (Eq,Show,Data,Typeable,Generic)
dealTermsNonGuaranteedFixedPriceTerms
:: DealTermsNonGuaranteedFixedPriceTerms
dealTermsNonGuaranteedFixedPriceTerms =
DealTermsNonGuaranteedFixedPriceTerms'
{ _dtngfptFixedPrices = Nothing
}
dtngfptFixedPrices :: Lens' DealTermsNonGuaranteedFixedPriceTerms [PricePerBuyer]
dtngfptFixedPrices
= lens _dtngfptFixedPrices
(\ s a -> s{_dtngfptFixedPrices = a})
. _Default
. _Coerce
instance FromJSON
DealTermsNonGuaranteedFixedPriceTerms where
parseJSON
= withObject "DealTermsNonGuaranteedFixedPriceTerms"
(\ o ->
DealTermsNonGuaranteedFixedPriceTerms' <$>
(o .:? "fixedPrices" .!= mempty))
instance ToJSON DealTermsNonGuaranteedFixedPriceTerms
where
toJSON DealTermsNonGuaranteedFixedPriceTerms'{..}
= object
(catMaybes
[("fixedPrices" .=) <$> _dtngfptFixedPrices])
data PerformanceReport = PerformanceReport'
{ _prFilteredBidRate :: !(Maybe (Textual Double))
, _prKind :: !Text
, _prLatency95thPercentile :: !(Maybe (Textual Double))
, _prCookieMatcherStatusRate :: !(Maybe [JSONValue])
, _prHostedMatchStatusRate :: !(Maybe [JSONValue])
, _prUnsuccessfulRequestRate :: !(Maybe (Textual Double))
, _prBidRequestRate :: !(Maybe (Textual Double))
, _prQuotaThrottledLimit :: !(Maybe (Textual Double))
, _prQuotaConfiguredLimit :: !(Maybe (Textual Double))
, _prSuccessfulRequestRate :: !(Maybe (Textual Double))
, _prLatency85thPercentile :: !(Maybe (Textual Double))
, _prCalloutStatusRate :: !(Maybe [JSONValue])
, _prLatency50thPercentile :: !(Maybe (Textual Double))
, _prBidRate :: !(Maybe (Textual Double))
, _prCreativeStatusRate :: !(Maybe [JSONValue])
, _prNoQuotaInRegion :: !(Maybe (Textual Double))
, _prRegion :: !(Maybe Text)
, _prInventoryMatchRate :: !(Maybe (Textual Double))
, _prPixelMatchResponses :: !(Maybe (Textual Double))
, _prTimestamp :: !(Maybe (Textual Int64))
, _prPixelMatchRequests :: !(Maybe (Textual Double))
, _prOutOfQuota :: !(Maybe (Textual Double))
} deriving (Eq,Show,Data,Typeable,Generic)
performanceReport
:: PerformanceReport
performanceReport =
PerformanceReport'
{ _prFilteredBidRate = Nothing
, _prKind = "adexchangebuyer#performanceReport"
, _prLatency95thPercentile = Nothing
, _prCookieMatcherStatusRate = Nothing
, _prHostedMatchStatusRate = Nothing
, _prUnsuccessfulRequestRate = Nothing
, _prBidRequestRate = Nothing
, _prQuotaThrottledLimit = Nothing
, _prQuotaConfiguredLimit = Nothing
, _prSuccessfulRequestRate = Nothing
, _prLatency85thPercentile = Nothing
, _prCalloutStatusRate = Nothing
, _prLatency50thPercentile = Nothing
, _prBidRate = Nothing
, _prCreativeStatusRate = Nothing
, _prNoQuotaInRegion = Nothing
, _prRegion = Nothing
, _prInventoryMatchRate = Nothing
, _prPixelMatchResponses = Nothing
, _prTimestamp = Nothing
, _prPixelMatchRequests = Nothing
, _prOutOfQuota = Nothing
}
prFilteredBidRate :: Lens' PerformanceReport (Maybe Double)
prFilteredBidRate
= lens _prFilteredBidRate
(\ s a -> s{_prFilteredBidRate = a})
. mapping _Coerce
prKind :: Lens' PerformanceReport Text
prKind = lens _prKind (\ s a -> s{_prKind = a})
prLatency95thPercentile :: Lens' PerformanceReport (Maybe Double)
prLatency95thPercentile
= lens _prLatency95thPercentile
(\ s a -> s{_prLatency95thPercentile = a})
. mapping _Coerce
prCookieMatcherStatusRate :: Lens' PerformanceReport [JSONValue]
prCookieMatcherStatusRate
= lens _prCookieMatcherStatusRate
(\ s a -> s{_prCookieMatcherStatusRate = a})
. _Default
. _Coerce
prHostedMatchStatusRate :: Lens' PerformanceReport [JSONValue]
prHostedMatchStatusRate
= lens _prHostedMatchStatusRate
(\ s a -> s{_prHostedMatchStatusRate = a})
. _Default
. _Coerce
prUnsuccessfulRequestRate :: Lens' PerformanceReport (Maybe Double)
prUnsuccessfulRequestRate
= lens _prUnsuccessfulRequestRate
(\ s a -> s{_prUnsuccessfulRequestRate = a})
. mapping _Coerce
prBidRequestRate :: Lens' PerformanceReport (Maybe Double)
prBidRequestRate
= lens _prBidRequestRate
(\ s a -> s{_prBidRequestRate = a})
. mapping _Coerce
prQuotaThrottledLimit :: Lens' PerformanceReport (Maybe Double)
prQuotaThrottledLimit
= lens _prQuotaThrottledLimit
(\ s a -> s{_prQuotaThrottledLimit = a})
. mapping _Coerce
prQuotaConfiguredLimit :: Lens' PerformanceReport (Maybe Double)
prQuotaConfiguredLimit
= lens _prQuotaConfiguredLimit
(\ s a -> s{_prQuotaConfiguredLimit = a})
. mapping _Coerce
prSuccessfulRequestRate :: Lens' PerformanceReport (Maybe Double)
prSuccessfulRequestRate
= lens _prSuccessfulRequestRate
(\ s a -> s{_prSuccessfulRequestRate = a})
. mapping _Coerce
prLatency85thPercentile :: Lens' PerformanceReport (Maybe Double)
prLatency85thPercentile
= lens _prLatency85thPercentile
(\ s a -> s{_prLatency85thPercentile = a})
. mapping _Coerce
prCalloutStatusRate :: Lens' PerformanceReport [JSONValue]
prCalloutStatusRate
= lens _prCalloutStatusRate
(\ s a -> s{_prCalloutStatusRate = a})
. _Default
. _Coerce
prLatency50thPercentile :: Lens' PerformanceReport (Maybe Double)
prLatency50thPercentile
= lens _prLatency50thPercentile
(\ s a -> s{_prLatency50thPercentile = a})
. mapping _Coerce
prBidRate :: Lens' PerformanceReport (Maybe Double)
prBidRate
= lens _prBidRate (\ s a -> s{_prBidRate = a}) .
mapping _Coerce
prCreativeStatusRate :: Lens' PerformanceReport [JSONValue]
prCreativeStatusRate
= lens _prCreativeStatusRate
(\ s a -> s{_prCreativeStatusRate = a})
. _Default
. _Coerce
prNoQuotaInRegion :: Lens' PerformanceReport (Maybe Double)
prNoQuotaInRegion
= lens _prNoQuotaInRegion
(\ s a -> s{_prNoQuotaInRegion = a})
. mapping _Coerce
prRegion :: Lens' PerformanceReport (Maybe Text)
prRegion = lens _prRegion (\ s a -> s{_prRegion = a})
prInventoryMatchRate :: Lens' PerformanceReport (Maybe Double)
prInventoryMatchRate
= lens _prInventoryMatchRate
(\ s a -> s{_prInventoryMatchRate = a})
. mapping _Coerce
prPixelMatchResponses :: Lens' PerformanceReport (Maybe Double)
prPixelMatchResponses
= lens _prPixelMatchResponses
(\ s a -> s{_prPixelMatchResponses = a})
. mapping _Coerce
prTimestamp :: Lens' PerformanceReport (Maybe Int64)
prTimestamp
= lens _prTimestamp (\ s a -> s{_prTimestamp = a}) .
mapping _Coerce
prPixelMatchRequests :: Lens' PerformanceReport (Maybe Double)
prPixelMatchRequests
= lens _prPixelMatchRequests
(\ s a -> s{_prPixelMatchRequests = a})
. mapping _Coerce
prOutOfQuota :: Lens' PerformanceReport (Maybe Double)
prOutOfQuota
= lens _prOutOfQuota (\ s a -> s{_prOutOfQuota = a})
. mapping _Coerce
instance FromJSON PerformanceReport where
parseJSON
= withObject "PerformanceReport"
(\ o ->
PerformanceReport' <$>
(o .:? "filteredBidRate") <*>
(o .:? "kind" .!=
"adexchangebuyer#performanceReport")
<*> (o .:? "latency95thPercentile")
<*> (o .:? "cookieMatcherStatusRate" .!= mempty)
<*> (o .:? "hostedMatchStatusRate" .!= mempty)
<*> (o .:? "unsuccessfulRequestRate")
<*> (o .:? "bidRequestRate")
<*> (o .:? "quotaThrottledLimit")
<*> (o .:? "quotaConfiguredLimit")
<*> (o .:? "successfulRequestRate")
<*> (o .:? "latency85thPercentile")
<*> (o .:? "calloutStatusRate" .!= mempty)
<*> (o .:? "latency50thPercentile")
<*> (o .:? "bidRate")
<*> (o .:? "creativeStatusRate" .!= mempty)
<*> (o .:? "noQuotaInRegion")
<*> (o .:? "region")
<*> (o .:? "inventoryMatchRate")
<*> (o .:? "pixelMatchResponses")
<*> (o .:? "timestamp")
<*> (o .:? "pixelMatchRequests")
<*> (o .:? "outOfQuota"))
instance ToJSON PerformanceReport where
toJSON PerformanceReport'{..}
= object
(catMaybes
[("filteredBidRate" .=) <$> _prFilteredBidRate,
Just ("kind" .= _prKind),
("latency95thPercentile" .=) <$>
_prLatency95thPercentile,
("cookieMatcherStatusRate" .=) <$>
_prCookieMatcherStatusRate,
("hostedMatchStatusRate" .=) <$>
_prHostedMatchStatusRate,
("unsuccessfulRequestRate" .=) <$>
_prUnsuccessfulRequestRate,
("bidRequestRate" .=) <$> _prBidRequestRate,
("quotaThrottledLimit" .=) <$>
_prQuotaThrottledLimit,
("quotaConfiguredLimit" .=) <$>
_prQuotaConfiguredLimit,
("successfulRequestRate" .=) <$>
_prSuccessfulRequestRate,
("latency85thPercentile" .=) <$>
_prLatency85thPercentile,
("calloutStatusRate" .=) <$> _prCalloutStatusRate,
("latency50thPercentile" .=) <$>
_prLatency50thPercentile,
("bidRate" .=) <$> _prBidRate,
("creativeStatusRate" .=) <$> _prCreativeStatusRate,
("noQuotaInRegion" .=) <$> _prNoQuotaInRegion,
("region" .=) <$> _prRegion,
("inventoryMatchRate" .=) <$> _prInventoryMatchRate,
("pixelMatchResponses" .=) <$>
_prPixelMatchResponses,
("timestamp" .=) <$> _prTimestamp,
("pixelMatchRequests" .=) <$> _prPixelMatchRequests,
("outOfQuota" .=) <$> _prOutOfQuota])
data PretargetingConfigExcludedPlacementsItem = PretargetingConfigExcludedPlacementsItem'
{ _pcepiToken :: !(Maybe Text)
, _pcepiType :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
pretargetingConfigExcludedPlacementsItem
:: PretargetingConfigExcludedPlacementsItem
pretargetingConfigExcludedPlacementsItem =
PretargetingConfigExcludedPlacementsItem'
{ _pcepiToken = Nothing
, _pcepiType = Nothing
}
pcepiToken :: Lens' PretargetingConfigExcludedPlacementsItem (Maybe Text)
pcepiToken
= lens _pcepiToken (\ s a -> s{_pcepiToken = a})
pcepiType :: Lens' PretargetingConfigExcludedPlacementsItem (Maybe Text)
pcepiType
= lens _pcepiType (\ s a -> s{_pcepiType = a})
instance FromJSON
PretargetingConfigExcludedPlacementsItem where
parseJSON
= withObject
"PretargetingConfigExcludedPlacementsItem"
(\ o ->
PretargetingConfigExcludedPlacementsItem' <$>
(o .:? "token") <*> (o .:? "type"))
instance ToJSON
PretargetingConfigExcludedPlacementsItem where
toJSON PretargetingConfigExcludedPlacementsItem'{..}
= object
(catMaybes
[("token" .=) <$> _pcepiToken,
("type" .=) <$> _pcepiType])
data Seller = Seller'
{ _sAccountId :: !(Maybe Text)
, _sSubAccountId :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
seller
:: Seller
seller =
Seller'
{ _sAccountId = Nothing
, _sSubAccountId = Nothing
}
sAccountId :: Lens' Seller (Maybe Text)
sAccountId
= lens _sAccountId (\ s a -> s{_sAccountId = a})
sSubAccountId :: Lens' Seller (Maybe Text)
sSubAccountId
= lens _sSubAccountId
(\ s a -> s{_sSubAccountId = a})
instance FromJSON Seller where
parseJSON
= withObject "Seller"
(\ o ->
Seller' <$>
(o .:? "accountId") <*> (o .:? "subAccountId"))
instance ToJSON Seller where
toJSON Seller'{..}
= object
(catMaybes
[("accountId" .=) <$> _sAccountId,
("subAccountId" .=) <$> _sSubAccountId])
data Account = Account'
{ _aMaximumTotalQps :: !(Maybe (Textual Int32))
, _aKind :: !Text
, _aCookieMatchingURL :: !(Maybe Text)
, _aMaximumActiveCreatives :: !(Maybe (Textual Int32))
, _aCookieMatchingNid :: !(Maybe Text)
, _aNumberActiveCreatives :: !(Maybe (Textual Int32))
, _aId :: !(Maybe (Textual Int32))
, _aBidderLocation :: !(Maybe [AccountBidderLocationItem])
} deriving (Eq,Show,Data,Typeable,Generic)
account
:: Account
account =
Account'
{ _aMaximumTotalQps = Nothing
, _aKind = "adexchangebuyer#account"
, _aCookieMatchingURL = Nothing
, _aMaximumActiveCreatives = Nothing
, _aCookieMatchingNid = Nothing
, _aNumberActiveCreatives = Nothing
, _aId = Nothing
, _aBidderLocation = Nothing
}
aMaximumTotalQps :: Lens' Account (Maybe Int32)
aMaximumTotalQps
= lens _aMaximumTotalQps
(\ s a -> s{_aMaximumTotalQps = a})
. mapping _Coerce
aKind :: Lens' Account Text
aKind = lens _aKind (\ s a -> s{_aKind = a})
aCookieMatchingURL :: Lens' Account (Maybe Text)
aCookieMatchingURL
= lens _aCookieMatchingURL
(\ s a -> s{_aCookieMatchingURL = a})
aMaximumActiveCreatives :: Lens' Account (Maybe Int32)
aMaximumActiveCreatives
= lens _aMaximumActiveCreatives
(\ s a -> s{_aMaximumActiveCreatives = a})
. mapping _Coerce
aCookieMatchingNid :: Lens' Account (Maybe Text)
aCookieMatchingNid
= lens _aCookieMatchingNid
(\ s a -> s{_aCookieMatchingNid = a})
aNumberActiveCreatives :: Lens' Account (Maybe Int32)
aNumberActiveCreatives
= lens _aNumberActiveCreatives
(\ s a -> s{_aNumberActiveCreatives = a})
. mapping _Coerce
aId :: Lens' Account (Maybe Int32)
aId
= lens _aId (\ s a -> s{_aId = a}) . mapping _Coerce
aBidderLocation :: Lens' Account [AccountBidderLocationItem]
aBidderLocation
= lens _aBidderLocation
(\ s a -> s{_aBidderLocation = a})
. _Default
. _Coerce
instance FromJSON Account where
parseJSON
= withObject "Account"
(\ o ->
Account' <$>
(o .:? "maximumTotalQps") <*>
(o .:? "kind" .!= "adexchangebuyer#account")
<*> (o .:? "cookieMatchingUrl")
<*> (o .:? "maximumActiveCreatives")
<*> (o .:? "cookieMatchingNid")
<*> (o .:? "numberActiveCreatives")
<*> (o .:? "id")
<*> (o .:? "bidderLocation" .!= mempty))
instance ToJSON Account where
toJSON Account'{..}
= object
(catMaybes
[("maximumTotalQps" .=) <$> _aMaximumTotalQps,
Just ("kind" .= _aKind),
("cookieMatchingUrl" .=) <$> _aCookieMatchingURL,
("maximumActiveCreatives" .=) <$>
_aMaximumActiveCreatives,
("cookieMatchingNid" .=) <$> _aCookieMatchingNid,
("numberActiveCreatives" .=) <$>
_aNumberActiveCreatives,
("id" .=) <$> _aId,
("bidderLocation" .=) <$> _aBidderLocation])
data DeleteOrderDealsRequest = DeleteOrderDealsRequest'
{ _dodrUpdateAction :: !(Maybe Text)
, _dodrDealIds :: !(Maybe [Text])
, _dodrProposalRevisionNumber :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
deleteOrderDealsRequest
:: DeleteOrderDealsRequest
deleteOrderDealsRequest =
DeleteOrderDealsRequest'
{ _dodrUpdateAction = Nothing
, _dodrDealIds = Nothing
, _dodrProposalRevisionNumber = Nothing
}
dodrUpdateAction :: Lens' DeleteOrderDealsRequest (Maybe Text)
dodrUpdateAction
= lens _dodrUpdateAction
(\ s a -> s{_dodrUpdateAction = a})
dodrDealIds :: Lens' DeleteOrderDealsRequest [Text]
dodrDealIds
= lens _dodrDealIds (\ s a -> s{_dodrDealIds = a}) .
_Default
. _Coerce
dodrProposalRevisionNumber :: Lens' DeleteOrderDealsRequest (Maybe Int64)
dodrProposalRevisionNumber
= lens _dodrProposalRevisionNumber
(\ s a -> s{_dodrProposalRevisionNumber = a})
. mapping _Coerce
instance FromJSON DeleteOrderDealsRequest where
parseJSON
= withObject "DeleteOrderDealsRequest"
(\ o ->
DeleteOrderDealsRequest' <$>
(o .:? "updateAction") <*>
(o .:? "dealIds" .!= mempty)
<*> (o .:? "proposalRevisionNumber"))
instance ToJSON DeleteOrderDealsRequest where
toJSON DeleteOrderDealsRequest'{..}
= object
(catMaybes
[("updateAction" .=) <$> _dodrUpdateAction,
("dealIds" .=) <$> _dodrDealIds,
("proposalRevisionNumber" .=) <$>
_dodrProposalRevisionNumber])
data ContactInformation = ContactInformation'
{ _ciEmail :: !(Maybe Text)
, _ciName :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
contactInformation
:: ContactInformation
contactInformation =
ContactInformation'
{ _ciEmail = Nothing
, _ciName = Nothing
}
ciEmail :: Lens' ContactInformation (Maybe Text)
ciEmail = lens _ciEmail (\ s a -> s{_ciEmail = a})
ciName :: Lens' ContactInformation (Maybe Text)
ciName = lens _ciName (\ s a -> s{_ciName = a})
instance FromJSON ContactInformation where
parseJSON
= withObject "ContactInformation"
(\ o ->
ContactInformation' <$>
(o .:? "email") <*> (o .:? "name"))
instance ToJSON ContactInformation where
toJSON ContactInformation'{..}
= object
(catMaybes
[("email" .=) <$> _ciEmail, ("name" .=) <$> _ciName])
data CreativeNATiveAdLogo = CreativeNATiveAdLogo'
{ _cnatalHeight :: !(Maybe (Textual Int32))
, _cnatalURL :: !(Maybe Text)
, _cnatalWidth :: !(Maybe (Textual Int32))
} deriving (Eq,Show,Data,Typeable,Generic)
creativeNATiveAdLogo
:: CreativeNATiveAdLogo
creativeNATiveAdLogo =
CreativeNATiveAdLogo'
{ _cnatalHeight = Nothing
, _cnatalURL = Nothing
, _cnatalWidth = Nothing
}
cnatalHeight :: Lens' CreativeNATiveAdLogo (Maybe Int32)
cnatalHeight
= lens _cnatalHeight (\ s a -> s{_cnatalHeight = a})
. mapping _Coerce
cnatalURL :: Lens' CreativeNATiveAdLogo (Maybe Text)
cnatalURL
= lens _cnatalURL (\ s a -> s{_cnatalURL = a})
cnatalWidth :: Lens' CreativeNATiveAdLogo (Maybe Int32)
cnatalWidth
= lens _cnatalWidth (\ s a -> s{_cnatalWidth = a}) .
mapping _Coerce
instance FromJSON CreativeNATiveAdLogo where
parseJSON
= withObject "CreativeNATiveAdLogo"
(\ o ->
CreativeNATiveAdLogo' <$>
(o .:? "height") <*> (o .:? "url") <*>
(o .:? "width"))
instance ToJSON CreativeNATiveAdLogo where
toJSON CreativeNATiveAdLogo'{..}
= object
(catMaybes
[("height" .=) <$> _cnatalHeight,
("url" .=) <$> _cnatalURL,
("width" .=) <$> _cnatalWidth])
newtype GetOrderDealsResponse = GetOrderDealsResponse'
{ _godrDeals :: Maybe [MarketplaceDeal]
} deriving (Eq,Show,Data,Typeable,Generic)
getOrderDealsResponse
:: GetOrderDealsResponse
getOrderDealsResponse =
GetOrderDealsResponse'
{ _godrDeals = Nothing
}
godrDeals :: Lens' GetOrderDealsResponse [MarketplaceDeal]
godrDeals
= lens _godrDeals (\ s a -> s{_godrDeals = a}) .
_Default
. _Coerce
instance FromJSON GetOrderDealsResponse where
parseJSON
= withObject "GetOrderDealsResponse"
(\ o ->
GetOrderDealsResponse' <$>
(o .:? "deals" .!= mempty))
instance ToJSON GetOrderDealsResponse where
toJSON GetOrderDealsResponse'{..}
= object (catMaybes [("deals" .=) <$> _godrDeals])
data PerformanceReportList = PerformanceReportList'
{ _prlKind :: !Text
, _prlPerformanceReport :: !(Maybe [PerformanceReport])
} deriving (Eq,Show,Data,Typeable,Generic)
performanceReportList
:: PerformanceReportList
performanceReportList =
PerformanceReportList'
{ _prlKind = "adexchangebuyer#performanceReportList"
, _prlPerformanceReport = Nothing
}
prlKind :: Lens' PerformanceReportList Text
prlKind = lens _prlKind (\ s a -> s{_prlKind = a})
prlPerformanceReport :: Lens' PerformanceReportList [PerformanceReport]
prlPerformanceReport
= lens _prlPerformanceReport
(\ s a -> s{_prlPerformanceReport = a})
. _Default
. _Coerce
instance FromJSON PerformanceReportList where
parseJSON
= withObject "PerformanceReportList"
(\ o ->
PerformanceReportList' <$>
(o .:? "kind" .!=
"adexchangebuyer#performanceReportList")
<*> (o .:? "performanceReport" .!= mempty))
instance ToJSON PerformanceReportList where
toJSON PerformanceReportList'{..}
= object
(catMaybes
[Just ("kind" .= _prlKind),
("performanceReport" .=) <$> _prlPerformanceReport])
data PretargetingConfig = PretargetingConfig'
{ _pcPlatforms :: !(Maybe [Text])
, _pcMobileCarriers :: !(Maybe [Textual Int64])
, _pcVendorTypes :: !(Maybe [Textual Int64])
, _pcExcludedGeoCriteriaIds :: !(Maybe [Textual Int64])
, _pcSupportedCreativeAttributes :: !(Maybe [Textual Int64])
, _pcUserLists :: !(Maybe [Textual Int64])
, _pcKind :: !Text
, _pcExcludedPlacements :: !(Maybe [PretargetingConfigExcludedPlacementsItem])
, _pcUserIdentifierDataRequired :: !(Maybe [Text])
, _pcMinimumViewabilityDecile :: !(Maybe (Textual Int32))
, _pcMobileDevices :: !(Maybe [Textual Int64])
, _pcLanguages :: !(Maybe [Text])
, _pcVerticals :: !(Maybe [Textual Int64])
, _pcVideoPlayerSizes :: !(Maybe [PretargetingConfigVideoPlayerSizesItem])
, _pcConfigId :: !(Maybe (Textual Int64))
, _pcPlacements :: !(Maybe [PretargetingConfigPlacementsItem])
, _pcExcludedUserLists :: !(Maybe [Textual Int64])
, _pcConfigName :: !(Maybe Text)
, _pcGeoCriteriaIds :: !(Maybe [Textual Int64])
, _pcDimensions :: !(Maybe [PretargetingConfigDimensionsItem])
, _pcExcludedVerticals :: !(Maybe [Textual Int64])
, _pcCreativeType :: !(Maybe [Text])
, _pcIsActive :: !(Maybe Bool)
, _pcExcludedContentLabels :: !(Maybe [Textual Int64])
, _pcBillingId :: !(Maybe (Textual Int64))
, _pcMobileOperatingSystemVersions :: !(Maybe [Textual Int64])
} deriving (Eq,Show,Data,Typeable,Generic)
pretargetingConfig
:: PretargetingConfig
pretargetingConfig =
PretargetingConfig'
{ _pcPlatforms = Nothing
, _pcMobileCarriers = Nothing
, _pcVendorTypes = Nothing
, _pcExcludedGeoCriteriaIds = Nothing
, _pcSupportedCreativeAttributes = Nothing
, _pcUserLists = Nothing
, _pcKind = "adexchangebuyer#pretargetingConfig"
, _pcExcludedPlacements = Nothing
, _pcUserIdentifierDataRequired = Nothing
, _pcMinimumViewabilityDecile = Nothing
, _pcMobileDevices = Nothing
, _pcLanguages = Nothing
, _pcVerticals = Nothing
, _pcVideoPlayerSizes = Nothing
, _pcConfigId = Nothing
, _pcPlacements = Nothing
, _pcExcludedUserLists = Nothing
, _pcConfigName = Nothing
, _pcGeoCriteriaIds = Nothing
, _pcDimensions = Nothing
, _pcExcludedVerticals = Nothing
, _pcCreativeType = Nothing
, _pcIsActive = Nothing
, _pcExcludedContentLabels = Nothing
, _pcBillingId = Nothing
, _pcMobileOperatingSystemVersions = Nothing
}
pcPlatforms :: Lens' PretargetingConfig [Text]
pcPlatforms
= lens _pcPlatforms (\ s a -> s{_pcPlatforms = a}) .
_Default
. _Coerce
pcMobileCarriers :: Lens' PretargetingConfig [Int64]
pcMobileCarriers
= lens _pcMobileCarriers
(\ s a -> s{_pcMobileCarriers = a})
. _Default
. _Coerce
pcVendorTypes :: Lens' PretargetingConfig [Int64]
pcVendorTypes
= lens _pcVendorTypes
(\ s a -> s{_pcVendorTypes = a})
. _Default
. _Coerce
pcExcludedGeoCriteriaIds :: Lens' PretargetingConfig [Int64]
pcExcludedGeoCriteriaIds
= lens _pcExcludedGeoCriteriaIds
(\ s a -> s{_pcExcludedGeoCriteriaIds = a})
. _Default
. _Coerce
pcSupportedCreativeAttributes :: Lens' PretargetingConfig [Int64]
pcSupportedCreativeAttributes
= lens _pcSupportedCreativeAttributes
(\ s a -> s{_pcSupportedCreativeAttributes = a})
. _Default
. _Coerce
pcUserLists :: Lens' PretargetingConfig [Int64]
pcUserLists
= lens _pcUserLists (\ s a -> s{_pcUserLists = a}) .
_Default
. _Coerce
pcKind :: Lens' PretargetingConfig Text
pcKind = lens _pcKind (\ s a -> s{_pcKind = a})
pcExcludedPlacements :: Lens' PretargetingConfig [PretargetingConfigExcludedPlacementsItem]
pcExcludedPlacements
= lens _pcExcludedPlacements
(\ s a -> s{_pcExcludedPlacements = a})
. _Default
. _Coerce
pcUserIdentifierDataRequired :: Lens' PretargetingConfig [Text]
pcUserIdentifierDataRequired
= lens _pcUserIdentifierDataRequired
(\ s a -> s{_pcUserIdentifierDataRequired = a})
. _Default
. _Coerce
pcMinimumViewabilityDecile :: Lens' PretargetingConfig (Maybe Int32)
pcMinimumViewabilityDecile
= lens _pcMinimumViewabilityDecile
(\ s a -> s{_pcMinimumViewabilityDecile = a})
. mapping _Coerce
pcMobileDevices :: Lens' PretargetingConfig [Int64]
pcMobileDevices
= lens _pcMobileDevices
(\ s a -> s{_pcMobileDevices = a})
. _Default
. _Coerce
pcLanguages :: Lens' PretargetingConfig [Text]
pcLanguages
= lens _pcLanguages (\ s a -> s{_pcLanguages = a}) .
_Default
. _Coerce
pcVerticals :: Lens' PretargetingConfig [Int64]
pcVerticals
= lens _pcVerticals (\ s a -> s{_pcVerticals = a}) .
_Default
. _Coerce
pcVideoPlayerSizes :: Lens' PretargetingConfig [PretargetingConfigVideoPlayerSizesItem]
pcVideoPlayerSizes
= lens _pcVideoPlayerSizes
(\ s a -> s{_pcVideoPlayerSizes = a})
. _Default
. _Coerce
pcConfigId :: Lens' PretargetingConfig (Maybe Int64)
pcConfigId
= lens _pcConfigId (\ s a -> s{_pcConfigId = a}) .
mapping _Coerce
pcPlacements :: Lens' PretargetingConfig [PretargetingConfigPlacementsItem]
pcPlacements
= lens _pcPlacements (\ s a -> s{_pcPlacements = a})
. _Default
. _Coerce
pcExcludedUserLists :: Lens' PretargetingConfig [Int64]
pcExcludedUserLists
= lens _pcExcludedUserLists
(\ s a -> s{_pcExcludedUserLists = a})
. _Default
. _Coerce
pcConfigName :: Lens' PretargetingConfig (Maybe Text)
pcConfigName
= lens _pcConfigName (\ s a -> s{_pcConfigName = a})
pcGeoCriteriaIds :: Lens' PretargetingConfig [Int64]
pcGeoCriteriaIds
= lens _pcGeoCriteriaIds
(\ s a -> s{_pcGeoCriteriaIds = a})
. _Default
. _Coerce
pcDimensions :: Lens' PretargetingConfig [PretargetingConfigDimensionsItem]
pcDimensions
= lens _pcDimensions (\ s a -> s{_pcDimensions = a})
. _Default
. _Coerce
pcExcludedVerticals :: Lens' PretargetingConfig [Int64]
pcExcludedVerticals
= lens _pcExcludedVerticals
(\ s a -> s{_pcExcludedVerticals = a})
. _Default
. _Coerce
pcCreativeType :: Lens' PretargetingConfig [Text]
pcCreativeType
= lens _pcCreativeType
(\ s a -> s{_pcCreativeType = a})
. _Default
. _Coerce
pcIsActive :: Lens' PretargetingConfig (Maybe Bool)
pcIsActive
= lens _pcIsActive (\ s a -> s{_pcIsActive = a})
pcExcludedContentLabels :: Lens' PretargetingConfig [Int64]
pcExcludedContentLabels
= lens _pcExcludedContentLabels
(\ s a -> s{_pcExcludedContentLabels = a})
. _Default
. _Coerce
pcBillingId :: Lens' PretargetingConfig (Maybe Int64)
pcBillingId
= lens _pcBillingId (\ s a -> s{_pcBillingId = a}) .
mapping _Coerce
pcMobileOperatingSystemVersions :: Lens' PretargetingConfig [Int64]
pcMobileOperatingSystemVersions
= lens _pcMobileOperatingSystemVersions
(\ s a -> s{_pcMobileOperatingSystemVersions = a})
. _Default
. _Coerce
instance FromJSON PretargetingConfig where
parseJSON
= withObject "PretargetingConfig"
(\ o ->
PretargetingConfig' <$>
(o .:? "platforms" .!= mempty) <*>
(o .:? "mobileCarriers" .!= mempty)
<*> (o .:? "vendorTypes" .!= mempty)
<*> (o .:? "excludedGeoCriteriaIds" .!= mempty)
<*> (o .:? "supportedCreativeAttributes" .!= mempty)
<*> (o .:? "userLists" .!= mempty)
<*>
(o .:? "kind" .!=
"adexchangebuyer#pretargetingConfig")
<*> (o .:? "excludedPlacements" .!= mempty)
<*> (o .:? "userIdentifierDataRequired" .!= mempty)
<*> (o .:? "minimumViewabilityDecile")
<*> (o .:? "mobileDevices" .!= mempty)
<*> (o .:? "languages" .!= mempty)
<*> (o .:? "verticals" .!= mempty)
<*> (o .:? "videoPlayerSizes" .!= mempty)
<*> (o .:? "configId")
<*> (o .:? "placements" .!= mempty)
<*> (o .:? "excludedUserLists" .!= mempty)
<*> (o .:? "configName")
<*> (o .:? "geoCriteriaIds" .!= mempty)
<*> (o .:? "dimensions" .!= mempty)
<*> (o .:? "excludedVerticals" .!= mempty)
<*> (o .:? "creativeType" .!= mempty)
<*> (o .:? "isActive")
<*> (o .:? "excludedContentLabels" .!= mempty)
<*> (o .:? "billingId")
<*>
(o .:? "mobileOperatingSystemVersions" .!= mempty))
instance ToJSON PretargetingConfig where
toJSON PretargetingConfig'{..}
= object
(catMaybes
[("platforms" .=) <$> _pcPlatforms,
("mobileCarriers" .=) <$> _pcMobileCarriers,
("vendorTypes" .=) <$> _pcVendorTypes,
("excludedGeoCriteriaIds" .=) <$>
_pcExcludedGeoCriteriaIds,
("supportedCreativeAttributes" .=) <$>
_pcSupportedCreativeAttributes,
("userLists" .=) <$> _pcUserLists,
Just ("kind" .= _pcKind),
("excludedPlacements" .=) <$> _pcExcludedPlacements,
("userIdentifierDataRequired" .=) <$>
_pcUserIdentifierDataRequired,
("minimumViewabilityDecile" .=) <$>
_pcMinimumViewabilityDecile,
("mobileDevices" .=) <$> _pcMobileDevices,
("languages" .=) <$> _pcLanguages,
("verticals" .=) <$> _pcVerticals,
("videoPlayerSizes" .=) <$> _pcVideoPlayerSizes,
("configId" .=) <$> _pcConfigId,
("placements" .=) <$> _pcPlacements,
("excludedUserLists" .=) <$> _pcExcludedUserLists,
("configName" .=) <$> _pcConfigName,
("geoCriteriaIds" .=) <$> _pcGeoCriteriaIds,
("dimensions" .=) <$> _pcDimensions,
("excludedVerticals" .=) <$> _pcExcludedVerticals,
("creativeType" .=) <$> _pcCreativeType,
("isActive" .=) <$> _pcIsActive,
("excludedContentLabels" .=) <$>
_pcExcludedContentLabels,
("billingId" .=) <$> _pcBillingId,
("mobileOperatingSystemVersions" .=) <$>
_pcMobileOperatingSystemVersions])
data CreativeFilteringReasons = CreativeFilteringReasons'
{ _cfrReasons :: !(Maybe [CreativeFilteringReasonsReasonsItem])
, _cfrDate :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
creativeFilteringReasons
:: CreativeFilteringReasons
creativeFilteringReasons =
CreativeFilteringReasons'
{ _cfrReasons = Nothing
, _cfrDate = Nothing
}
cfrReasons :: Lens' CreativeFilteringReasons [CreativeFilteringReasonsReasonsItem]
cfrReasons
= lens _cfrReasons (\ s a -> s{_cfrReasons = a}) .
_Default
. _Coerce
cfrDate :: Lens' CreativeFilteringReasons (Maybe Text)
cfrDate = lens _cfrDate (\ s a -> s{_cfrDate = a})
instance FromJSON CreativeFilteringReasons where
parseJSON
= withObject "CreativeFilteringReasons"
(\ o ->
CreativeFilteringReasons' <$>
(o .:? "reasons" .!= mempty) <*> (o .:? "date"))
instance ToJSON CreativeFilteringReasons where
toJSON CreativeFilteringReasons'{..}
= object
(catMaybes
[("reasons" .=) <$> _cfrReasons,
("date" .=) <$> _cfrDate])
data TargetingValueCreativeSize = TargetingValueCreativeSize'
{ _tvcsSize :: !(Maybe TargetingValueSize)
, _tvcsCompanionSizes :: !(Maybe [TargetingValueSize])
, _tvcsSkippableAdType :: !(Maybe Text)
, _tvcsCreativeSizeType :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
targetingValueCreativeSize
:: TargetingValueCreativeSize
targetingValueCreativeSize =
TargetingValueCreativeSize'
{ _tvcsSize = Nothing
, _tvcsCompanionSizes = Nothing
, _tvcsSkippableAdType = Nothing
, _tvcsCreativeSizeType = Nothing
}
tvcsSize :: Lens' TargetingValueCreativeSize (Maybe TargetingValueSize)
tvcsSize = lens _tvcsSize (\ s a -> s{_tvcsSize = a})
tvcsCompanionSizes :: Lens' TargetingValueCreativeSize [TargetingValueSize]
tvcsCompanionSizes
= lens _tvcsCompanionSizes
(\ s a -> s{_tvcsCompanionSizes = a})
. _Default
. _Coerce
tvcsSkippableAdType :: Lens' TargetingValueCreativeSize (Maybe Text)
tvcsSkippableAdType
= lens _tvcsSkippableAdType
(\ s a -> s{_tvcsSkippableAdType = a})
tvcsCreativeSizeType :: Lens' TargetingValueCreativeSize (Maybe Text)
tvcsCreativeSizeType
= lens _tvcsCreativeSizeType
(\ s a -> s{_tvcsCreativeSizeType = a})
instance FromJSON TargetingValueCreativeSize where
parseJSON
= withObject "TargetingValueCreativeSize"
(\ o ->
TargetingValueCreativeSize' <$>
(o .:? "size") <*>
(o .:? "companionSizes" .!= mempty)
<*> (o .:? "skippableAdType")
<*> (o .:? "creativeSizeType"))
instance ToJSON TargetingValueCreativeSize where
toJSON TargetingValueCreativeSize'{..}
= object
(catMaybes
[("size" .=) <$> _tvcsSize,
("companionSizes" .=) <$> _tvcsCompanionSizes,
("skippableAdType" .=) <$> _tvcsSkippableAdType,
("creativeSizeType" .=) <$> _tvcsCreativeSizeType])
data DealTermsGuaranteedFixedPriceTermsBillingInfo = DealTermsGuaranteedFixedPriceTermsBillingInfo'
{ _dtgfptbiCurrencyConversionTimeMs :: !(Maybe (Textual Int64))
, _dtgfptbiDfpLineItemId :: !(Maybe (Textual Int64))
, _dtgfptbiPrice :: !(Maybe Price)
, _dtgfptbiOriginalContractedQuantity :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
dealTermsGuaranteedFixedPriceTermsBillingInfo
:: DealTermsGuaranteedFixedPriceTermsBillingInfo
dealTermsGuaranteedFixedPriceTermsBillingInfo =
DealTermsGuaranteedFixedPriceTermsBillingInfo'
{ _dtgfptbiCurrencyConversionTimeMs = Nothing
, _dtgfptbiDfpLineItemId = Nothing
, _dtgfptbiPrice = Nothing
, _dtgfptbiOriginalContractedQuantity = Nothing
}
dtgfptbiCurrencyConversionTimeMs :: Lens' DealTermsGuaranteedFixedPriceTermsBillingInfo (Maybe Int64)
dtgfptbiCurrencyConversionTimeMs
= lens _dtgfptbiCurrencyConversionTimeMs
(\ s a -> s{_dtgfptbiCurrencyConversionTimeMs = a})
. mapping _Coerce
dtgfptbiDfpLineItemId :: Lens' DealTermsGuaranteedFixedPriceTermsBillingInfo (Maybe Int64)
dtgfptbiDfpLineItemId
= lens _dtgfptbiDfpLineItemId
(\ s a -> s{_dtgfptbiDfpLineItemId = a})
. mapping _Coerce
dtgfptbiPrice :: Lens' DealTermsGuaranteedFixedPriceTermsBillingInfo (Maybe Price)
dtgfptbiPrice
= lens _dtgfptbiPrice
(\ s a -> s{_dtgfptbiPrice = a})
dtgfptbiOriginalContractedQuantity :: Lens' DealTermsGuaranteedFixedPriceTermsBillingInfo (Maybe Int64)
dtgfptbiOriginalContractedQuantity
= lens _dtgfptbiOriginalContractedQuantity
(\ s a -> s{_dtgfptbiOriginalContractedQuantity = a})
. mapping _Coerce
instance FromJSON
DealTermsGuaranteedFixedPriceTermsBillingInfo where
parseJSON
= withObject
"DealTermsGuaranteedFixedPriceTermsBillingInfo"
(\ o ->
DealTermsGuaranteedFixedPriceTermsBillingInfo' <$>
(o .:? "currencyConversionTimeMs") <*>
(o .:? "dfpLineItemId")
<*> (o .:? "price")
<*> (o .:? "originalContractedQuantity"))
instance ToJSON
DealTermsGuaranteedFixedPriceTermsBillingInfo where
toJSON
DealTermsGuaranteedFixedPriceTermsBillingInfo'{..}
= object
(catMaybes
[("currencyConversionTimeMs" .=) <$>
_dtgfptbiCurrencyConversionTimeMs,
("dfpLineItemId" .=) <$> _dtgfptbiDfpLineItemId,
("price" .=) <$> _dtgfptbiPrice,
("originalContractedQuantity" .=) <$>
_dtgfptbiOriginalContractedQuantity])
newtype GetPublisherProFilesByAccountIdResponse = GetPublisherProFilesByAccountIdResponse'
{ _gppfbairProFiles :: Maybe [PublisherProFileAPIProto]
} deriving (Eq,Show,Data,Typeable,Generic)
getPublisherProFilesByAccountIdResponse
:: GetPublisherProFilesByAccountIdResponse
getPublisherProFilesByAccountIdResponse =
GetPublisherProFilesByAccountIdResponse'
{ _gppfbairProFiles = Nothing
}
gppfbairProFiles :: Lens' GetPublisherProFilesByAccountIdResponse [PublisherProFileAPIProto]
gppfbairProFiles
= lens _gppfbairProFiles
(\ s a -> s{_gppfbairProFiles = a})
. _Default
. _Coerce
instance FromJSON
GetPublisherProFilesByAccountIdResponse where
parseJSON
= withObject
"GetPublisherProFilesByAccountIdResponse"
(\ o ->
GetPublisherProFilesByAccountIdResponse' <$>
(o .:? "profiles" .!= mempty))
instance ToJSON
GetPublisherProFilesByAccountIdResponse where
toJSON GetPublisherProFilesByAccountIdResponse'{..}
= object
(catMaybes [("profiles" .=) <$> _gppfbairProFiles])
data Proposal = Proposal'
{ _pBuyerPrivateData :: !(Maybe PrivateData)
, _pIsSetupComplete :: !(Maybe Bool)
, _pInventorySource :: !(Maybe Text)
, _pBuyerContacts :: !(Maybe [ContactInformation])
, _pKind :: !Text
, _pOriginatorRole :: !(Maybe Text)
, _pDBmAdvertiserIds :: !(Maybe [Text])
, _pRevisionNumber :: !(Maybe (Textual Int64))
, _pBilledBuyer :: !(Maybe Buyer)
, _pPrivateAuctionId :: !(Maybe Text)
, _pIsRenegotiating :: !(Maybe Bool)
, _pHasSellerSignedOff :: !(Maybe Bool)
, _pSeller :: !(Maybe Seller)
, _pProposalId :: !(Maybe Text)
, _pName :: !(Maybe Text)
, _pSellerContacts :: !(Maybe [ContactInformation])
, _pLabels :: !(Maybe [MarketplaceLabel])
, _pRevisionTimeMs :: !(Maybe (Textual Int64))
, _pProposalState :: !(Maybe Text)
, _pLastUpdaterOrCommentorRole :: !(Maybe Text)
, _pNegotiationId :: !(Maybe Text)
, _pHasBuyerSignedOff :: !(Maybe Bool)
, _pBuyer :: !(Maybe Buyer)
} deriving (Eq,Show,Data,Typeable,Generic)
proposal
:: Proposal
proposal =
Proposal'
{ _pBuyerPrivateData = Nothing
, _pIsSetupComplete = Nothing
, _pInventorySource = Nothing
, _pBuyerContacts = Nothing
, _pKind = "adexchangebuyer#proposal"
, _pOriginatorRole = Nothing
, _pDBmAdvertiserIds = Nothing
, _pRevisionNumber = Nothing
, _pBilledBuyer = Nothing
, _pPrivateAuctionId = Nothing
, _pIsRenegotiating = Nothing
, _pHasSellerSignedOff = Nothing
, _pSeller = Nothing
, _pProposalId = Nothing
, _pName = Nothing
, _pSellerContacts = Nothing
, _pLabels = Nothing
, _pRevisionTimeMs = Nothing
, _pProposalState = Nothing
, _pLastUpdaterOrCommentorRole = Nothing
, _pNegotiationId = Nothing
, _pHasBuyerSignedOff = Nothing
, _pBuyer = Nothing
}
pBuyerPrivateData :: Lens' Proposal (Maybe PrivateData)
pBuyerPrivateData
= lens _pBuyerPrivateData
(\ s a -> s{_pBuyerPrivateData = a})
pIsSetupComplete :: Lens' Proposal (Maybe Bool)
pIsSetupComplete
= lens _pIsSetupComplete
(\ s a -> s{_pIsSetupComplete = a})
pInventorySource :: Lens' Proposal (Maybe Text)
pInventorySource
= lens _pInventorySource
(\ s a -> s{_pInventorySource = a})
pBuyerContacts :: Lens' Proposal [ContactInformation]
pBuyerContacts
= lens _pBuyerContacts
(\ s a -> s{_pBuyerContacts = a})
. _Default
. _Coerce
pKind :: Lens' Proposal Text
pKind = lens _pKind (\ s a -> s{_pKind = a})
pOriginatorRole :: Lens' Proposal (Maybe Text)
pOriginatorRole
= lens _pOriginatorRole
(\ s a -> s{_pOriginatorRole = a})
pDBmAdvertiserIds :: Lens' Proposal [Text]
pDBmAdvertiserIds
= lens _pDBmAdvertiserIds
(\ s a -> s{_pDBmAdvertiserIds = a})
. _Default
. _Coerce
pRevisionNumber :: Lens' Proposal (Maybe Int64)
pRevisionNumber
= lens _pRevisionNumber
(\ s a -> s{_pRevisionNumber = a})
. mapping _Coerce
pBilledBuyer :: Lens' Proposal (Maybe Buyer)
pBilledBuyer
= lens _pBilledBuyer (\ s a -> s{_pBilledBuyer = a})
pPrivateAuctionId :: Lens' Proposal (Maybe Text)
pPrivateAuctionId
= lens _pPrivateAuctionId
(\ s a -> s{_pPrivateAuctionId = a})
pIsRenegotiating :: Lens' Proposal (Maybe Bool)
pIsRenegotiating
= lens _pIsRenegotiating
(\ s a -> s{_pIsRenegotiating = a})
pHasSellerSignedOff :: Lens' Proposal (Maybe Bool)
pHasSellerSignedOff
= lens _pHasSellerSignedOff
(\ s a -> s{_pHasSellerSignedOff = a})
pSeller :: Lens' Proposal (Maybe Seller)
pSeller = lens _pSeller (\ s a -> s{_pSeller = a})
pProposalId :: Lens' Proposal (Maybe Text)
pProposalId
= lens _pProposalId (\ s a -> s{_pProposalId = a})
pName :: Lens' Proposal (Maybe Text)
pName = lens _pName (\ s a -> s{_pName = a})
pSellerContacts :: Lens' Proposal [ContactInformation]
pSellerContacts
= lens _pSellerContacts
(\ s a -> s{_pSellerContacts = a})
. _Default
. _Coerce
pLabels :: Lens' Proposal [MarketplaceLabel]
pLabels
= lens _pLabels (\ s a -> s{_pLabels = a}) . _Default
. _Coerce
pRevisionTimeMs :: Lens' Proposal (Maybe Int64)
pRevisionTimeMs
= lens _pRevisionTimeMs
(\ s a -> s{_pRevisionTimeMs = a})
. mapping _Coerce
pProposalState :: Lens' Proposal (Maybe Text)
pProposalState
= lens _pProposalState
(\ s a -> s{_pProposalState = a})
pLastUpdaterOrCommentorRole :: Lens' Proposal (Maybe Text)
pLastUpdaterOrCommentorRole
= lens _pLastUpdaterOrCommentorRole
(\ s a -> s{_pLastUpdaterOrCommentorRole = a})
pNegotiationId :: Lens' Proposal (Maybe Text)
pNegotiationId
= lens _pNegotiationId
(\ s a -> s{_pNegotiationId = a})
pHasBuyerSignedOff :: Lens' Proposal (Maybe Bool)
pHasBuyerSignedOff
= lens _pHasBuyerSignedOff
(\ s a -> s{_pHasBuyerSignedOff = a})
pBuyer :: Lens' Proposal (Maybe Buyer)
pBuyer = lens _pBuyer (\ s a -> s{_pBuyer = a})
instance FromJSON Proposal where
parseJSON
= withObject "Proposal"
(\ o ->
Proposal' <$>
(o .:? "buyerPrivateData") <*>
(o .:? "isSetupComplete")
<*> (o .:? "inventorySource")
<*> (o .:? "buyerContacts" .!= mempty)
<*> (o .:? "kind" .!= "adexchangebuyer#proposal")
<*> (o .:? "originatorRole")
<*> (o .:? "dbmAdvertiserIds" .!= mempty)
<*> (o .:? "revisionNumber")
<*> (o .:? "billedBuyer")
<*> (o .:? "privateAuctionId")
<*> (o .:? "isRenegotiating")
<*> (o .:? "hasSellerSignedOff")
<*> (o .:? "seller")
<*> (o .:? "proposalId")
<*> (o .:? "name")
<*> (o .:? "sellerContacts" .!= mempty)
<*> (o .:? "labels" .!= mempty)
<*> (o .:? "revisionTimeMs")
<*> (o .:? "proposalState")
<*> (o .:? "lastUpdaterOrCommentorRole")
<*> (o .:? "negotiationId")
<*> (o .:? "hasBuyerSignedOff")
<*> (o .:? "buyer"))
instance ToJSON Proposal where
toJSON Proposal'{..}
= object
(catMaybes
[("buyerPrivateData" .=) <$> _pBuyerPrivateData,
("isSetupComplete" .=) <$> _pIsSetupComplete,
("inventorySource" .=) <$> _pInventorySource,
("buyerContacts" .=) <$> _pBuyerContacts,
Just ("kind" .= _pKind),
("originatorRole" .=) <$> _pOriginatorRole,
("dbmAdvertiserIds" .=) <$> _pDBmAdvertiserIds,
("revisionNumber" .=) <$> _pRevisionNumber,
("billedBuyer" .=) <$> _pBilledBuyer,
("privateAuctionId" .=) <$> _pPrivateAuctionId,
("isRenegotiating" .=) <$> _pIsRenegotiating,
("hasSellerSignedOff" .=) <$> _pHasSellerSignedOff,
("seller" .=) <$> _pSeller,
("proposalId" .=) <$> _pProposalId,
("name" .=) <$> _pName,
("sellerContacts" .=) <$> _pSellerContacts,
("labels" .=) <$> _pLabels,
("revisionTimeMs" .=) <$> _pRevisionTimeMs,
("proposalState" .=) <$> _pProposalState,
("lastUpdaterOrCommentorRole" .=) <$>
_pLastUpdaterOrCommentorRole,
("negotiationId" .=) <$> _pNegotiationId,
("hasBuyerSignedOff" .=) <$> _pHasBuyerSignedOff,
("buyer" .=) <$> _pBuyer])
data BillingInfoList = BillingInfoList'
{ _bilKind :: !Text
, _bilItems :: !(Maybe [BillingInfo])
} deriving (Eq,Show,Data,Typeable,Generic)
billingInfoList
:: BillingInfoList
billingInfoList =
BillingInfoList'
{ _bilKind = "adexchangebuyer#billingInfoList"
, _bilItems = Nothing
}
bilKind :: Lens' BillingInfoList Text
bilKind = lens _bilKind (\ s a -> s{_bilKind = a})
bilItems :: Lens' BillingInfoList [BillingInfo]
bilItems
= lens _bilItems (\ s a -> s{_bilItems = a}) .
_Default
. _Coerce
instance FromJSON BillingInfoList where
parseJSON
= withObject "BillingInfoList"
(\ o ->
BillingInfoList' <$>
(o .:? "kind" .!= "adexchangebuyer#billingInfoList")
<*> (o .:? "items" .!= mempty))
instance ToJSON BillingInfoList where
toJSON BillingInfoList'{..}
= object
(catMaybes
[Just ("kind" .= _bilKind),
("items" .=) <$> _bilItems])
newtype AddOrderNotesResponse = AddOrderNotesResponse'
{ _aNotes :: Maybe [MarketplaceNote]
} deriving (Eq,Show,Data,Typeable,Generic)
addOrderNotesResponse
:: AddOrderNotesResponse
addOrderNotesResponse =
AddOrderNotesResponse'
{ _aNotes = Nothing
}
aNotes :: Lens' AddOrderNotesResponse [MarketplaceNote]
aNotes
= lens _aNotes (\ s a -> s{_aNotes = a}) . _Default .
_Coerce
instance FromJSON AddOrderNotesResponse where
parseJSON
= withObject "AddOrderNotesResponse"
(\ o ->
AddOrderNotesResponse' <$>
(o .:? "notes" .!= mempty))
instance ToJSON AddOrderNotesResponse where
toJSON AddOrderNotesResponse'{..}
= object (catMaybes [("notes" .=) <$> _aNotes])
data TargetingValueSize = TargetingValueSize'
{ _tvsHeight :: !(Maybe (Textual Int32))
, _tvsWidth :: !(Maybe (Textual Int32))
} deriving (Eq,Show,Data,Typeable,Generic)
targetingValueSize
:: TargetingValueSize
targetingValueSize =
TargetingValueSize'
{ _tvsHeight = Nothing
, _tvsWidth = Nothing
}
tvsHeight :: Lens' TargetingValueSize (Maybe Int32)
tvsHeight
= lens _tvsHeight (\ s a -> s{_tvsHeight = a}) .
mapping _Coerce
tvsWidth :: Lens' TargetingValueSize (Maybe Int32)
tvsWidth
= lens _tvsWidth (\ s a -> s{_tvsWidth = a}) .
mapping _Coerce
instance FromJSON TargetingValueSize where
parseJSON
= withObject "TargetingValueSize"
(\ o ->
TargetingValueSize' <$>
(o .:? "height") <*> (o .:? "width"))
instance ToJSON TargetingValueSize where
toJSON TargetingValueSize'{..}
= object
(catMaybes
[("height" .=) <$> _tvsHeight,
("width" .=) <$> _tvsWidth])
data UpdatePrivateAuctionProposalRequest = UpdatePrivateAuctionProposalRequest'
{ _upaprExternalDealId :: !(Maybe Text)
, _upaprUpdateAction :: !(Maybe Text)
, _upaprNote :: !(Maybe MarketplaceNote)
, _upaprProposalRevisionNumber :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
updatePrivateAuctionProposalRequest
:: UpdatePrivateAuctionProposalRequest
updatePrivateAuctionProposalRequest =
UpdatePrivateAuctionProposalRequest'
{ _upaprExternalDealId = Nothing
, _upaprUpdateAction = Nothing
, _upaprNote = Nothing
, _upaprProposalRevisionNumber = Nothing
}
upaprExternalDealId :: Lens' UpdatePrivateAuctionProposalRequest (Maybe Text)
upaprExternalDealId
= lens _upaprExternalDealId
(\ s a -> s{_upaprExternalDealId = a})
upaprUpdateAction :: Lens' UpdatePrivateAuctionProposalRequest (Maybe Text)
upaprUpdateAction
= lens _upaprUpdateAction
(\ s a -> s{_upaprUpdateAction = a})
upaprNote :: Lens' UpdatePrivateAuctionProposalRequest (Maybe MarketplaceNote)
upaprNote
= lens _upaprNote (\ s a -> s{_upaprNote = a})
upaprProposalRevisionNumber :: Lens' UpdatePrivateAuctionProposalRequest (Maybe Int64)
upaprProposalRevisionNumber
= lens _upaprProposalRevisionNumber
(\ s a -> s{_upaprProposalRevisionNumber = a})
. mapping _Coerce
instance FromJSON UpdatePrivateAuctionProposalRequest
where
parseJSON
= withObject "UpdatePrivateAuctionProposalRequest"
(\ o ->
UpdatePrivateAuctionProposalRequest' <$>
(o .:? "externalDealId") <*> (o .:? "updateAction")
<*> (o .:? "note")
<*> (o .:? "proposalRevisionNumber"))
instance ToJSON UpdatePrivateAuctionProposalRequest
where
toJSON UpdatePrivateAuctionProposalRequest'{..}
= object
(catMaybes
[("externalDealId" .=) <$> _upaprExternalDealId,
("updateAction" .=) <$> _upaprUpdateAction,
("note" .=) <$> _upaprNote,
("proposalRevisionNumber" .=) <$>
_upaprProposalRevisionNumber])
data PretargetingConfigDimensionsItem = PretargetingConfigDimensionsItem'
{ _pcdiHeight :: !(Maybe (Textual Int64))
, _pcdiWidth :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
pretargetingConfigDimensionsItem
:: PretargetingConfigDimensionsItem
pretargetingConfigDimensionsItem =
PretargetingConfigDimensionsItem'
{ _pcdiHeight = Nothing
, _pcdiWidth = Nothing
}
pcdiHeight :: Lens' PretargetingConfigDimensionsItem (Maybe Int64)
pcdiHeight
= lens _pcdiHeight (\ s a -> s{_pcdiHeight = a}) .
mapping _Coerce
pcdiWidth :: Lens' PretargetingConfigDimensionsItem (Maybe Int64)
pcdiWidth
= lens _pcdiWidth (\ s a -> s{_pcdiWidth = a}) .
mapping _Coerce
instance FromJSON PretargetingConfigDimensionsItem
where
parseJSON
= withObject "PretargetingConfigDimensionsItem"
(\ o ->
PretargetingConfigDimensionsItem' <$>
(o .:? "height") <*> (o .:? "width"))
instance ToJSON PretargetingConfigDimensionsItem
where
toJSON PretargetingConfigDimensionsItem'{..}
= object
(catMaybes
[("height" .=) <$> _pcdiHeight,
("width" .=) <$> _pcdiWidth])
data CreativeCorrectionsItemContextsItem = CreativeCorrectionsItemContextsItem'
{ _cciciPlatform :: !(Maybe [Text])
, _cciciContextType :: !(Maybe Text)
, _cciciAuctionType :: !(Maybe [Text])
, _cciciGeoCriteriaId :: !(Maybe [Textual Int32])
} deriving (Eq,Show,Data,Typeable,Generic)
creativeCorrectionsItemContextsItem
:: CreativeCorrectionsItemContextsItem
creativeCorrectionsItemContextsItem =
CreativeCorrectionsItemContextsItem'
{ _cciciPlatform = Nothing
, _cciciContextType = Nothing
, _cciciAuctionType = Nothing
, _cciciGeoCriteriaId = Nothing
}
cciciPlatform :: Lens' CreativeCorrectionsItemContextsItem [Text]
cciciPlatform
= lens _cciciPlatform
(\ s a -> s{_cciciPlatform = a})
. _Default
. _Coerce
cciciContextType :: Lens' CreativeCorrectionsItemContextsItem (Maybe Text)
cciciContextType
= lens _cciciContextType
(\ s a -> s{_cciciContextType = a})
cciciAuctionType :: Lens' CreativeCorrectionsItemContextsItem [Text]
cciciAuctionType
= lens _cciciAuctionType
(\ s a -> s{_cciciAuctionType = a})
. _Default
. _Coerce
cciciGeoCriteriaId :: Lens' CreativeCorrectionsItemContextsItem [Int32]
cciciGeoCriteriaId
= lens _cciciGeoCriteriaId
(\ s a -> s{_cciciGeoCriteriaId = a})
. _Default
. _Coerce
instance FromJSON CreativeCorrectionsItemContextsItem
where
parseJSON
= withObject "CreativeCorrectionsItemContextsItem"
(\ o ->
CreativeCorrectionsItemContextsItem' <$>
(o .:? "platform" .!= mempty) <*>
(o .:? "contextType")
<*> (o .:? "auctionType" .!= mempty)
<*> (o .:? "geoCriteriaId" .!= mempty))
instance ToJSON CreativeCorrectionsItemContextsItem
where
toJSON CreativeCorrectionsItemContextsItem'{..}
= object
(catMaybes
[("platform" .=) <$> _cciciPlatform,
("contextType" .=) <$> _cciciContextType,
("auctionType" .=) <$> _cciciAuctionType,
("geoCriteriaId" .=) <$> _cciciGeoCriteriaId])
data PublisherProvidedForecast = PublisherProvidedForecast'
{ _ppfWeeklyImpressions :: !(Maybe (Textual Int64))
, _ppfWeeklyUniques :: !(Maybe (Textual Int64))
, _ppfDimensions :: !(Maybe [Dimension])
} deriving (Eq,Show,Data,Typeable,Generic)
publisherProvidedForecast
:: PublisherProvidedForecast
publisherProvidedForecast =
PublisherProvidedForecast'
{ _ppfWeeklyImpressions = Nothing
, _ppfWeeklyUniques = Nothing
, _ppfDimensions = Nothing
}
ppfWeeklyImpressions :: Lens' PublisherProvidedForecast (Maybe Int64)
ppfWeeklyImpressions
= lens _ppfWeeklyImpressions
(\ s a -> s{_ppfWeeklyImpressions = a})
. mapping _Coerce
ppfWeeklyUniques :: Lens' PublisherProvidedForecast (Maybe Int64)
ppfWeeklyUniques
= lens _ppfWeeklyUniques
(\ s a -> s{_ppfWeeklyUniques = a})
. mapping _Coerce
ppfDimensions :: Lens' PublisherProvidedForecast [Dimension]
ppfDimensions
= lens _ppfDimensions
(\ s a -> s{_ppfDimensions = a})
. _Default
. _Coerce
instance FromJSON PublisherProvidedForecast where
parseJSON
= withObject "PublisherProvidedForecast"
(\ o ->
PublisherProvidedForecast' <$>
(o .:? "weeklyImpressions") <*>
(o .:? "weeklyUniques")
<*> (o .:? "dimensions" .!= mempty))
instance ToJSON PublisherProvidedForecast where
toJSON PublisherProvidedForecast'{..}
= object
(catMaybes
[("weeklyImpressions" .=) <$> _ppfWeeklyImpressions,
("weeklyUniques" .=) <$> _ppfWeeklyUniques,
("dimensions" .=) <$> _ppfDimensions])
data TargetingValue = TargetingValue'
{ _tvCreativeSizeValue :: !(Maybe TargetingValueCreativeSize)
, _tvStringValue :: !(Maybe Text)
, _tvLongValue :: !(Maybe (Textual Int64))
, _tvDayPartTargetingValue :: !(Maybe TargetingValueDayPartTargeting)
} deriving (Eq,Show,Data,Typeable,Generic)
targetingValue
:: TargetingValue
targetingValue =
TargetingValue'
{ _tvCreativeSizeValue = Nothing
, _tvStringValue = Nothing
, _tvLongValue = Nothing
, _tvDayPartTargetingValue = Nothing
}
tvCreativeSizeValue :: Lens' TargetingValue (Maybe TargetingValueCreativeSize)
tvCreativeSizeValue
= lens _tvCreativeSizeValue
(\ s a -> s{_tvCreativeSizeValue = a})
tvStringValue :: Lens' TargetingValue (Maybe Text)
tvStringValue
= lens _tvStringValue
(\ s a -> s{_tvStringValue = a})
tvLongValue :: Lens' TargetingValue (Maybe Int64)
tvLongValue
= lens _tvLongValue (\ s a -> s{_tvLongValue = a}) .
mapping _Coerce
tvDayPartTargetingValue :: Lens' TargetingValue (Maybe TargetingValueDayPartTargeting)
tvDayPartTargetingValue
= lens _tvDayPartTargetingValue
(\ s a -> s{_tvDayPartTargetingValue = a})
instance FromJSON TargetingValue where
parseJSON
= withObject "TargetingValue"
(\ o ->
TargetingValue' <$>
(o .:? "creativeSizeValue") <*> (o .:? "stringValue")
<*> (o .:? "longValue")
<*> (o .:? "dayPartTargetingValue"))
instance ToJSON TargetingValue where
toJSON TargetingValue'{..}
= object
(catMaybes
[("creativeSizeValue" .=) <$> _tvCreativeSizeValue,
("stringValue" .=) <$> _tvStringValue,
("longValue" .=) <$> _tvLongValue,
("dayPartTargetingValue" .=) <$>
_tvDayPartTargetingValue])
data CreativeNATiveAdAppIcon = CreativeNATiveAdAppIcon'
{ _cnataaiHeight :: !(Maybe (Textual Int32))
, _cnataaiURL :: !(Maybe Text)
, _cnataaiWidth :: !(Maybe (Textual Int32))
} deriving (Eq,Show,Data,Typeable,Generic)
creativeNATiveAdAppIcon
:: CreativeNATiveAdAppIcon
creativeNATiveAdAppIcon =
CreativeNATiveAdAppIcon'
{ _cnataaiHeight = Nothing
, _cnataaiURL = Nothing
, _cnataaiWidth = Nothing
}
cnataaiHeight :: Lens' CreativeNATiveAdAppIcon (Maybe Int32)
cnataaiHeight
= lens _cnataaiHeight
(\ s a -> s{_cnataaiHeight = a})
. mapping _Coerce
cnataaiURL :: Lens' CreativeNATiveAdAppIcon (Maybe Text)
cnataaiURL
= lens _cnataaiURL (\ s a -> s{_cnataaiURL = a})
cnataaiWidth :: Lens' CreativeNATiveAdAppIcon (Maybe Int32)
cnataaiWidth
= lens _cnataaiWidth (\ s a -> s{_cnataaiWidth = a})
. mapping _Coerce
instance FromJSON CreativeNATiveAdAppIcon where
parseJSON
= withObject "CreativeNATiveAdAppIcon"
(\ o ->
CreativeNATiveAdAppIcon' <$>
(o .:? "height") <*> (o .:? "url") <*>
(o .:? "width"))
instance ToJSON CreativeNATiveAdAppIcon where
toJSON CreativeNATiveAdAppIcon'{..}
= object
(catMaybes
[("height" .=) <$> _cnataaiHeight,
("url" .=) <$> _cnataaiURL,
("width" .=) <$> _cnataaiWidth])
data Price = Price'
{ _pCurrencyCode :: !(Maybe Text)
, _pAmountMicros :: !(Maybe (Textual Double))
, _pPricingType :: !(Maybe Text)
, _pExpectedCpmMicros :: !(Maybe (Textual Double))
} deriving (Eq,Show,Data,Typeable,Generic)
price
:: Price
price =
Price'
{ _pCurrencyCode = Nothing
, _pAmountMicros = Nothing
, _pPricingType = Nothing
, _pExpectedCpmMicros = Nothing
}
pCurrencyCode :: Lens' Price (Maybe Text)
pCurrencyCode
= lens _pCurrencyCode
(\ s a -> s{_pCurrencyCode = a})
pAmountMicros :: Lens' Price (Maybe Double)
pAmountMicros
= lens _pAmountMicros
(\ s a -> s{_pAmountMicros = a})
. mapping _Coerce
pPricingType :: Lens' Price (Maybe Text)
pPricingType
= lens _pPricingType (\ s a -> s{_pPricingType = a})
pExpectedCpmMicros :: Lens' Price (Maybe Double)
pExpectedCpmMicros
= lens _pExpectedCpmMicros
(\ s a -> s{_pExpectedCpmMicros = a})
. mapping _Coerce
instance FromJSON Price where
parseJSON
= withObject "Price"
(\ o ->
Price' <$>
(o .:? "currencyCode") <*> (o .:? "amountMicros") <*>
(o .:? "pricingType")
<*> (o .:? "expectedCpmMicros"))
instance ToJSON Price where
toJSON Price'{..}
= object
(catMaybes
[("currencyCode" .=) <$> _pCurrencyCode,
("amountMicros" .=) <$> _pAmountMicros,
("pricingType" .=) <$> _pPricingType,
("expectedCpmMicros" .=) <$> _pExpectedCpmMicros])
data PretargetingConfigVideoPlayerSizesItem = PretargetingConfigVideoPlayerSizesItem'
{ _pcvpsiMinWidth :: !(Maybe (Textual Int64))
, _pcvpsiAspectRatio :: !(Maybe Text)
, _pcvpsiMinHeight :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
pretargetingConfigVideoPlayerSizesItem
:: PretargetingConfigVideoPlayerSizesItem
pretargetingConfigVideoPlayerSizesItem =
PretargetingConfigVideoPlayerSizesItem'
{ _pcvpsiMinWidth = Nothing
, _pcvpsiAspectRatio = Nothing
, _pcvpsiMinHeight = Nothing
}
pcvpsiMinWidth :: Lens' PretargetingConfigVideoPlayerSizesItem (Maybe Int64)
pcvpsiMinWidth
= lens _pcvpsiMinWidth
(\ s a -> s{_pcvpsiMinWidth = a})
. mapping _Coerce
pcvpsiAspectRatio :: Lens' PretargetingConfigVideoPlayerSizesItem (Maybe Text)
pcvpsiAspectRatio
= lens _pcvpsiAspectRatio
(\ s a -> s{_pcvpsiAspectRatio = a})
pcvpsiMinHeight :: Lens' PretargetingConfigVideoPlayerSizesItem (Maybe Int64)
pcvpsiMinHeight
= lens _pcvpsiMinHeight
(\ s a -> s{_pcvpsiMinHeight = a})
. mapping _Coerce
instance FromJSON
PretargetingConfigVideoPlayerSizesItem where
parseJSON
= withObject "PretargetingConfigVideoPlayerSizesItem"
(\ o ->
PretargetingConfigVideoPlayerSizesItem' <$>
(o .:? "minWidth") <*> (o .:? "aspectRatio") <*>
(o .:? "minHeight"))
instance ToJSON
PretargetingConfigVideoPlayerSizesItem where
toJSON PretargetingConfigVideoPlayerSizesItem'{..}
= object
(catMaybes
[("minWidth" .=) <$> _pcvpsiMinWidth,
("aspectRatio" .=) <$> _pcvpsiAspectRatio,
("minHeight" .=) <$> _pcvpsiMinHeight])
data EditAllOrderDealsRequest = EditAllOrderDealsRequest'
{ _eUpdateAction :: !(Maybe Text)
, _eDeals :: !(Maybe [MarketplaceDeal])
, _eProposalRevisionNumber :: !(Maybe (Textual Int64))
, _eProposal :: !(Maybe Proposal)
} deriving (Eq,Show,Data,Typeable,Generic)
editAllOrderDealsRequest
:: EditAllOrderDealsRequest
editAllOrderDealsRequest =
EditAllOrderDealsRequest'
{ _eUpdateAction = Nothing
, _eDeals = Nothing
, _eProposalRevisionNumber = Nothing
, _eProposal = Nothing
}
eUpdateAction :: Lens' EditAllOrderDealsRequest (Maybe Text)
eUpdateAction
= lens _eUpdateAction
(\ s a -> s{_eUpdateAction = a})
eDeals :: Lens' EditAllOrderDealsRequest [MarketplaceDeal]
eDeals
= lens _eDeals (\ s a -> s{_eDeals = a}) . _Default .
_Coerce
eProposalRevisionNumber :: Lens' EditAllOrderDealsRequest (Maybe Int64)
eProposalRevisionNumber
= lens _eProposalRevisionNumber
(\ s a -> s{_eProposalRevisionNumber = a})
. mapping _Coerce
eProposal :: Lens' EditAllOrderDealsRequest (Maybe Proposal)
eProposal
= lens _eProposal (\ s a -> s{_eProposal = a})
instance FromJSON EditAllOrderDealsRequest where
parseJSON
= withObject "EditAllOrderDealsRequest"
(\ o ->
EditAllOrderDealsRequest' <$>
(o .:? "updateAction") <*> (o .:? "deals" .!= mempty)
<*> (o .:? "proposalRevisionNumber")
<*> (o .:? "proposal"))
instance ToJSON EditAllOrderDealsRequest where
toJSON EditAllOrderDealsRequest'{..}
= object
(catMaybes
[("updateAction" .=) <$> _eUpdateAction,
("deals" .=) <$> _eDeals,
("proposalRevisionNumber" .=) <$>
_eProposalRevisionNumber,
("proposal" .=) <$> _eProposal])
data BillingInfo = BillingInfo'
{ _biKind :: !Text
, _biAccountName :: !(Maybe Text)
, _biAccountId :: !(Maybe (Textual Int32))
, _biBillingId :: !(Maybe [Text])
} deriving (Eq,Show,Data,Typeable,Generic)
billingInfo
:: BillingInfo
billingInfo =
BillingInfo'
{ _biKind = "adexchangebuyer#billingInfo"
, _biAccountName = Nothing
, _biAccountId = Nothing
, _biBillingId = Nothing
}
biKind :: Lens' BillingInfo Text
biKind = lens _biKind (\ s a -> s{_biKind = a})
biAccountName :: Lens' BillingInfo (Maybe Text)
biAccountName
= lens _biAccountName
(\ s a -> s{_biAccountName = a})
biAccountId :: Lens' BillingInfo (Maybe Int32)
biAccountId
= lens _biAccountId (\ s a -> s{_biAccountId = a}) .
mapping _Coerce
biBillingId :: Lens' BillingInfo [Text]
biBillingId
= lens _biBillingId (\ s a -> s{_biBillingId = a}) .
_Default
. _Coerce
instance FromJSON BillingInfo where
parseJSON
= withObject "BillingInfo"
(\ o ->
BillingInfo' <$>
(o .:? "kind" .!= "adexchangebuyer#billingInfo") <*>
(o .:? "accountName")
<*> (o .:? "accountId")
<*> (o .:? "billingId" .!= mempty))
instance ToJSON BillingInfo where
toJSON BillingInfo'{..}
= object
(catMaybes
[Just ("kind" .= _biKind),
("accountName" .=) <$> _biAccountName,
("accountId" .=) <$> _biAccountId,
("billingId" .=) <$> _biBillingId])
data TargetingValueDayPartTargeting = TargetingValueDayPartTargeting'
{ _tvdptTimeZoneType :: !(Maybe Text)
, _tvdptDayParts :: !(Maybe [TargetingValueDayPartTargetingDayPart])
} deriving (Eq,Show,Data,Typeable,Generic)
targetingValueDayPartTargeting
:: TargetingValueDayPartTargeting
targetingValueDayPartTargeting =
TargetingValueDayPartTargeting'
{ _tvdptTimeZoneType = Nothing
, _tvdptDayParts = Nothing
}
tvdptTimeZoneType :: Lens' TargetingValueDayPartTargeting (Maybe Text)
tvdptTimeZoneType
= lens _tvdptTimeZoneType
(\ s a -> s{_tvdptTimeZoneType = a})
tvdptDayParts :: Lens' TargetingValueDayPartTargeting [TargetingValueDayPartTargetingDayPart]
tvdptDayParts
= lens _tvdptDayParts
(\ s a -> s{_tvdptDayParts = a})
. _Default
. _Coerce
instance FromJSON TargetingValueDayPartTargeting
where
parseJSON
= withObject "TargetingValueDayPartTargeting"
(\ o ->
TargetingValueDayPartTargeting' <$>
(o .:? "timeZoneType") <*>
(o .:? "dayParts" .!= mempty))
instance ToJSON TargetingValueDayPartTargeting where
toJSON TargetingValueDayPartTargeting'{..}
= object
(catMaybes
[("timeZoneType" .=) <$> _tvdptTimeZoneType,
("dayParts" .=) <$> _tvdptDayParts])
data SharedTargeting = SharedTargeting'
{ _stKey :: !(Maybe Text)
, _stExclusions :: !(Maybe [TargetingValue])
, _stInclusions :: !(Maybe [TargetingValue])
} deriving (Eq,Show,Data,Typeable,Generic)
sharedTargeting
:: SharedTargeting
sharedTargeting =
SharedTargeting'
{ _stKey = Nothing
, _stExclusions = Nothing
, _stInclusions = Nothing
}
stKey :: Lens' SharedTargeting (Maybe Text)
stKey = lens _stKey (\ s a -> s{_stKey = a})
stExclusions :: Lens' SharedTargeting [TargetingValue]
stExclusions
= lens _stExclusions (\ s a -> s{_stExclusions = a})
. _Default
. _Coerce
stInclusions :: Lens' SharedTargeting [TargetingValue]
stInclusions
= lens _stInclusions (\ s a -> s{_stInclusions = a})
. _Default
. _Coerce
instance FromJSON SharedTargeting where
parseJSON
= withObject "SharedTargeting"
(\ o ->
SharedTargeting' <$>
(o .:? "key") <*> (o .:? "exclusions" .!= mempty) <*>
(o .:? "inclusions" .!= mempty))
instance ToJSON SharedTargeting where
toJSON SharedTargeting'{..}
= object
(catMaybes
[("key" .=) <$> _stKey,
("exclusions" .=) <$> _stExclusions,
("inclusions" .=) <$> _stInclusions])
data CreativeNATiveAdImage = CreativeNATiveAdImage'
{ _cnataiHeight :: !(Maybe (Textual Int32))
, _cnataiURL :: !(Maybe Text)
, _cnataiWidth :: !(Maybe (Textual Int32))
} deriving (Eq,Show,Data,Typeable,Generic)
creativeNATiveAdImage
:: CreativeNATiveAdImage
creativeNATiveAdImage =
CreativeNATiveAdImage'
{ _cnataiHeight = Nothing
, _cnataiURL = Nothing
, _cnataiWidth = Nothing
}
cnataiHeight :: Lens' CreativeNATiveAdImage (Maybe Int32)
cnataiHeight
= lens _cnataiHeight (\ s a -> s{_cnataiHeight = a})
. mapping _Coerce
cnataiURL :: Lens' CreativeNATiveAdImage (Maybe Text)
cnataiURL
= lens _cnataiURL (\ s a -> s{_cnataiURL = a})
cnataiWidth :: Lens' CreativeNATiveAdImage (Maybe Int32)
cnataiWidth
= lens _cnataiWidth (\ s a -> s{_cnataiWidth = a}) .
mapping _Coerce
instance FromJSON CreativeNATiveAdImage where
parseJSON
= withObject "CreativeNATiveAdImage"
(\ o ->
CreativeNATiveAdImage' <$>
(o .:? "height") <*> (o .:? "url") <*>
(o .:? "width"))
instance ToJSON CreativeNATiveAdImage where
toJSON CreativeNATiveAdImage'{..}
= object
(catMaybes
[("height" .=) <$> _cnataiHeight,
("url" .=) <$> _cnataiURL,
("width" .=) <$> _cnataiWidth])
data Product = Product'
{ _proState :: !(Maybe Text)
, _proInventorySource :: !(Maybe Text)
, _proWebPropertyCode :: !(Maybe Text)
, _proCreationTimeMs :: !(Maybe (Textual Int64))
, _proTerms :: !(Maybe DealTerms)
, _proLastUpdateTimeMs :: !(Maybe (Textual Int64))
, _proKind :: !Text
, _proRevisionNumber :: !(Maybe (Textual Int64))
, _proPrivateAuctionId :: !(Maybe Text)
, _proDeliveryControl :: !(Maybe DeliveryControl)
, _proHasCreatorSignedOff :: !(Maybe Bool)
, _proFlightStartTimeMs :: !(Maybe (Textual Int64))
, _proSharedTargetings :: !(Maybe [SharedTargeting])
, _proSeller :: !(Maybe Seller)
, _proSyndicationProduct :: !(Maybe Text)
, _proFlightEndTimeMs :: !(Maybe (Textual Int64))
, _proName :: !(Maybe Text)
, _proCreatorContacts :: !(Maybe [ContactInformation])
, _proMarketplacePublisherProFileId :: !(Maybe Text)
, _proPublisherProvidedForecast :: !(Maybe PublisherProvidedForecast)
, _proLabels :: !(Maybe [MarketplaceLabel])
, _proPublisherProFileId :: !(Maybe Text)
, _proLegacyOfferId :: !(Maybe Text)
, _proProductId :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
product
:: Product
product =
Product'
{ _proState = Nothing
, _proInventorySource = Nothing
, _proWebPropertyCode = Nothing
, _proCreationTimeMs = Nothing
, _proTerms = Nothing
, _proLastUpdateTimeMs = Nothing
, _proKind = "adexchangebuyer#product"
, _proRevisionNumber = Nothing
, _proPrivateAuctionId = Nothing
, _proDeliveryControl = Nothing
, _proHasCreatorSignedOff = Nothing
, _proFlightStartTimeMs = Nothing
, _proSharedTargetings = Nothing
, _proSeller = Nothing
, _proSyndicationProduct = Nothing
, _proFlightEndTimeMs = Nothing
, _proName = Nothing
, _proCreatorContacts = Nothing
, _proMarketplacePublisherProFileId = Nothing
, _proPublisherProvidedForecast = Nothing
, _proLabels = Nothing
, _proPublisherProFileId = Nothing
, _proLegacyOfferId = Nothing
, _proProductId = Nothing
}
proState :: Lens' Product (Maybe Text)
proState = lens _proState (\ s a -> s{_proState = a})
proInventorySource :: Lens' Product (Maybe Text)
proInventorySource
= lens _proInventorySource
(\ s a -> s{_proInventorySource = a})
proWebPropertyCode :: Lens' Product (Maybe Text)
proWebPropertyCode
= lens _proWebPropertyCode
(\ s a -> s{_proWebPropertyCode = a})
proCreationTimeMs :: Lens' Product (Maybe Int64)
proCreationTimeMs
= lens _proCreationTimeMs
(\ s a -> s{_proCreationTimeMs = a})
. mapping _Coerce
proTerms :: Lens' Product (Maybe DealTerms)
proTerms = lens _proTerms (\ s a -> s{_proTerms = a})
proLastUpdateTimeMs :: Lens' Product (Maybe Int64)
proLastUpdateTimeMs
= lens _proLastUpdateTimeMs
(\ s a -> s{_proLastUpdateTimeMs = a})
. mapping _Coerce
proKind :: Lens' Product Text
proKind = lens _proKind (\ s a -> s{_proKind = a})
proRevisionNumber :: Lens' Product (Maybe Int64)
proRevisionNumber
= lens _proRevisionNumber
(\ s a -> s{_proRevisionNumber = a})
. mapping _Coerce
proPrivateAuctionId :: Lens' Product (Maybe Text)
proPrivateAuctionId
= lens _proPrivateAuctionId
(\ s a -> s{_proPrivateAuctionId = a})
proDeliveryControl :: Lens' Product (Maybe DeliveryControl)
proDeliveryControl
= lens _proDeliveryControl
(\ s a -> s{_proDeliveryControl = a})
proHasCreatorSignedOff :: Lens' Product (Maybe Bool)
proHasCreatorSignedOff
= lens _proHasCreatorSignedOff
(\ s a -> s{_proHasCreatorSignedOff = a})
proFlightStartTimeMs :: Lens' Product (Maybe Int64)
proFlightStartTimeMs
= lens _proFlightStartTimeMs
(\ s a -> s{_proFlightStartTimeMs = a})
. mapping _Coerce
proSharedTargetings :: Lens' Product [SharedTargeting]
proSharedTargetings
= lens _proSharedTargetings
(\ s a -> s{_proSharedTargetings = a})
. _Default
. _Coerce
proSeller :: Lens' Product (Maybe Seller)
proSeller
= lens _proSeller (\ s a -> s{_proSeller = a})
proSyndicationProduct :: Lens' Product (Maybe Text)
proSyndicationProduct
= lens _proSyndicationProduct
(\ s a -> s{_proSyndicationProduct = a})
proFlightEndTimeMs :: Lens' Product (Maybe Int64)
proFlightEndTimeMs
= lens _proFlightEndTimeMs
(\ s a -> s{_proFlightEndTimeMs = a})
. mapping _Coerce
proName :: Lens' Product (Maybe Text)
proName = lens _proName (\ s a -> s{_proName = a})
proCreatorContacts :: Lens' Product [ContactInformation]
proCreatorContacts
= lens _proCreatorContacts
(\ s a -> s{_proCreatorContacts = a})
. _Default
. _Coerce
proMarketplacePublisherProFileId :: Lens' Product (Maybe Text)
proMarketplacePublisherProFileId
= lens _proMarketplacePublisherProFileId
(\ s a -> s{_proMarketplacePublisherProFileId = a})
proPublisherProvidedForecast :: Lens' Product (Maybe PublisherProvidedForecast)
proPublisherProvidedForecast
= lens _proPublisherProvidedForecast
(\ s a -> s{_proPublisherProvidedForecast = a})
proLabels :: Lens' Product [MarketplaceLabel]
proLabels
= lens _proLabels (\ s a -> s{_proLabels = a}) .
_Default
. _Coerce
proPublisherProFileId :: Lens' Product (Maybe Text)
proPublisherProFileId
= lens _proPublisherProFileId
(\ s a -> s{_proPublisherProFileId = a})
proLegacyOfferId :: Lens' Product (Maybe Text)
proLegacyOfferId
= lens _proLegacyOfferId
(\ s a -> s{_proLegacyOfferId = a})
proProductId :: Lens' Product (Maybe Text)
proProductId
= lens _proProductId (\ s a -> s{_proProductId = a})
instance FromJSON Product where
parseJSON
= withObject "Product"
(\ o ->
Product' <$>
(o .:? "state") <*> (o .:? "inventorySource") <*>
(o .:? "webPropertyCode")
<*> (o .:? "creationTimeMs")
<*> (o .:? "terms")
<*> (o .:? "lastUpdateTimeMs")
<*> (o .:? "kind" .!= "adexchangebuyer#product")
<*> (o .:? "revisionNumber")
<*> (o .:? "privateAuctionId")
<*> (o .:? "deliveryControl")
<*> (o .:? "hasCreatorSignedOff")
<*> (o .:? "flightStartTimeMs")
<*> (o .:? "sharedTargetings" .!= mempty)
<*> (o .:? "seller")
<*> (o .:? "syndicationProduct")
<*> (o .:? "flightEndTimeMs")
<*> (o .:? "name")
<*> (o .:? "creatorContacts" .!= mempty)
<*> (o .:? "marketplacePublisherProfileId")
<*> (o .:? "publisherProvidedForecast")
<*> (o .:? "labels" .!= mempty)
<*> (o .:? "publisherProfileId")
<*> (o .:? "legacyOfferId")
<*> (o .:? "productId"))
instance ToJSON Product where
toJSON Product'{..}
= object
(catMaybes
[("state" .=) <$> _proState,
("inventorySource" .=) <$> _proInventorySource,
("webPropertyCode" .=) <$> _proWebPropertyCode,
("creationTimeMs" .=) <$> _proCreationTimeMs,
("terms" .=) <$> _proTerms,
("lastUpdateTimeMs" .=) <$> _proLastUpdateTimeMs,
Just ("kind" .= _proKind),
("revisionNumber" .=) <$> _proRevisionNumber,
("privateAuctionId" .=) <$> _proPrivateAuctionId,
("deliveryControl" .=) <$> _proDeliveryControl,
("hasCreatorSignedOff" .=) <$>
_proHasCreatorSignedOff,
("flightStartTimeMs" .=) <$> _proFlightStartTimeMs,
("sharedTargetings" .=) <$> _proSharedTargetings,
("seller" .=) <$> _proSeller,
("syndicationProduct" .=) <$> _proSyndicationProduct,
("flightEndTimeMs" .=) <$> _proFlightEndTimeMs,
("name" .=) <$> _proName,
("creatorContacts" .=) <$> _proCreatorContacts,
("marketplacePublisherProfileId" .=) <$>
_proMarketplacePublisherProFileId,
("publisherProvidedForecast" .=) <$>
_proPublisherProvidedForecast,
("labels" .=) <$> _proLabels,
("publisherProfileId" .=) <$> _proPublisherProFileId,
("legacyOfferId" .=) <$> _proLegacyOfferId,
("productId" .=) <$> _proProductId])
data CreativeServingRestrictionsItem = CreativeServingRestrictionsItem'
{ _csriContexts :: !(Maybe [CreativeServingRestrictionsItemContextsItem])
, _csriReason :: !(Maybe Text)
, _csriDisApprovalReasons :: !(Maybe [CreativeServingRestrictionsItemDisApprovalReasonsItem])
} deriving (Eq,Show,Data,Typeable,Generic)
creativeServingRestrictionsItem
:: CreativeServingRestrictionsItem
creativeServingRestrictionsItem =
CreativeServingRestrictionsItem'
{ _csriContexts = Nothing
, _csriReason = Nothing
, _csriDisApprovalReasons = Nothing
}
csriContexts :: Lens' CreativeServingRestrictionsItem [CreativeServingRestrictionsItemContextsItem]
csriContexts
= lens _csriContexts (\ s a -> s{_csriContexts = a})
. _Default
. _Coerce
csriReason :: Lens' CreativeServingRestrictionsItem (Maybe Text)
csriReason
= lens _csriReason (\ s a -> s{_csriReason = a})
csriDisApprovalReasons :: Lens' CreativeServingRestrictionsItem [CreativeServingRestrictionsItemDisApprovalReasonsItem]
csriDisApprovalReasons
= lens _csriDisApprovalReasons
(\ s a -> s{_csriDisApprovalReasons = a})
. _Default
. _Coerce
instance FromJSON CreativeServingRestrictionsItem
where
parseJSON
= withObject "CreativeServingRestrictionsItem"
(\ o ->
CreativeServingRestrictionsItem' <$>
(o .:? "contexts" .!= mempty) <*> (o .:? "reason")
<*> (o .:? "disapprovalReasons" .!= mempty))
instance ToJSON CreativeServingRestrictionsItem where
toJSON CreativeServingRestrictionsItem'{..}
= object
(catMaybes
[("contexts" .=) <$> _csriContexts,
("reason" .=) <$> _csriReason,
("disapprovalReasons" .=) <$>
_csriDisApprovalReasons])
data DeleteOrderDealsResponse = DeleteOrderDealsResponse'
{ _dDeals :: !(Maybe [MarketplaceDeal])
, _dProposalRevisionNumber :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
deleteOrderDealsResponse
:: DeleteOrderDealsResponse
deleteOrderDealsResponse =
DeleteOrderDealsResponse'
{ _dDeals = Nothing
, _dProposalRevisionNumber = Nothing
}
dDeals :: Lens' DeleteOrderDealsResponse [MarketplaceDeal]
dDeals
= lens _dDeals (\ s a -> s{_dDeals = a}) . _Default .
_Coerce
dProposalRevisionNumber :: Lens' DeleteOrderDealsResponse (Maybe Int64)
dProposalRevisionNumber
= lens _dProposalRevisionNumber
(\ s a -> s{_dProposalRevisionNumber = a})
. mapping _Coerce
instance FromJSON DeleteOrderDealsResponse where
parseJSON
= withObject "DeleteOrderDealsResponse"
(\ o ->
DeleteOrderDealsResponse' <$>
(o .:? "deals" .!= mempty) <*>
(o .:? "proposalRevisionNumber"))
instance ToJSON DeleteOrderDealsResponse where
toJSON DeleteOrderDealsResponse'{..}
= object
(catMaybes
[("deals" .=) <$> _dDeals,
("proposalRevisionNumber" .=) <$>
_dProposalRevisionNumber])
data PretargetingConfigPlacementsItem = PretargetingConfigPlacementsItem'
{ _pcpiToken :: !(Maybe Text)
, _pcpiType :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
pretargetingConfigPlacementsItem
:: PretargetingConfigPlacementsItem
pretargetingConfigPlacementsItem =
PretargetingConfigPlacementsItem'
{ _pcpiToken = Nothing
, _pcpiType = Nothing
}
pcpiToken :: Lens' PretargetingConfigPlacementsItem (Maybe Text)
pcpiToken
= lens _pcpiToken (\ s a -> s{_pcpiToken = a})
pcpiType :: Lens' PretargetingConfigPlacementsItem (Maybe Text)
pcpiType = lens _pcpiType (\ s a -> s{_pcpiType = a})
instance FromJSON PretargetingConfigPlacementsItem
where
parseJSON
= withObject "PretargetingConfigPlacementsItem"
(\ o ->
PretargetingConfigPlacementsItem' <$>
(o .:? "token") <*> (o .:? "type"))
instance ToJSON PretargetingConfigPlacementsItem
where
toJSON PretargetingConfigPlacementsItem'{..}
= object
(catMaybes
[("token" .=) <$> _pcpiToken,
("type" .=) <$> _pcpiType])
data PublisherProFileAPIProto = PublisherProFileAPIProto'
{ _ppfapAudience :: !(Maybe Text)
, _ppfapState :: !(Maybe Text)
, _ppfapMediaKitLink :: !(Maybe Text)
, _ppfapDirectContact :: !(Maybe Text)
, _ppfapSamplePageLink :: !(Maybe Text)
, _ppfapLogoURL :: !(Maybe Text)
, _ppfapKind :: !Text
, _ppfapExchange :: !(Maybe Text)
, _ppfapOverview :: !(Maybe Text)
, _ppfapGooglePlusLink :: !(Maybe Text)
, _ppfapProFileId :: !(Maybe (Textual Int32))
, _ppfapIsParent :: !(Maybe Bool)
, _ppfapSeller :: !(Maybe Seller)
, _ppfapAccountId :: !(Maybe Text)
, _ppfapName :: !(Maybe Text)
, _ppfapBuyerPitchStatement :: !(Maybe Text)
, _ppfapPublisherProvidedForecast :: !(Maybe PublisherProvidedForecast)
, _ppfapIsPublished :: !(Maybe Bool)
, _ppfapPublisherDomains :: !(Maybe [Text])
, _ppfapPublisherProFileId :: !(Maybe Text)
, _ppfapRateCardInfoLink :: !(Maybe Text)
, _ppfapTopHeadlines :: !(Maybe [Text])
, _ppfapProgrammaticContact :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
publisherProFileAPIProto
:: PublisherProFileAPIProto
publisherProFileAPIProto =
PublisherProFileAPIProto'
{ _ppfapAudience = Nothing
, _ppfapState = Nothing
, _ppfapMediaKitLink = Nothing
, _ppfapDirectContact = Nothing
, _ppfapSamplePageLink = Nothing
, _ppfapLogoURL = Nothing
, _ppfapKind = "adexchangebuyer#publisherProfileApiProto"
, _ppfapExchange = Nothing
, _ppfapOverview = Nothing
, _ppfapGooglePlusLink = Nothing
, _ppfapProFileId = Nothing
, _ppfapIsParent = Nothing
, _ppfapSeller = Nothing
, _ppfapAccountId = Nothing
, _ppfapName = Nothing
, _ppfapBuyerPitchStatement = Nothing
, _ppfapPublisherProvidedForecast = Nothing
, _ppfapIsPublished = Nothing
, _ppfapPublisherDomains = Nothing
, _ppfapPublisherProFileId = Nothing
, _ppfapRateCardInfoLink = Nothing
, _ppfapTopHeadlines = Nothing
, _ppfapProgrammaticContact = Nothing
}
ppfapAudience :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapAudience
= lens _ppfapAudience
(\ s a -> s{_ppfapAudience = a})
ppfapState :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapState
= lens _ppfapState (\ s a -> s{_ppfapState = a})
ppfapMediaKitLink :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapMediaKitLink
= lens _ppfapMediaKitLink
(\ s a -> s{_ppfapMediaKitLink = a})
ppfapDirectContact :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapDirectContact
= lens _ppfapDirectContact
(\ s a -> s{_ppfapDirectContact = a})
ppfapSamplePageLink :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapSamplePageLink
= lens _ppfapSamplePageLink
(\ s a -> s{_ppfapSamplePageLink = a})
ppfapLogoURL :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapLogoURL
= lens _ppfapLogoURL (\ s a -> s{_ppfapLogoURL = a})
ppfapKind :: Lens' PublisherProFileAPIProto Text
ppfapKind
= lens _ppfapKind (\ s a -> s{_ppfapKind = a})
ppfapExchange :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapExchange
= lens _ppfapExchange
(\ s a -> s{_ppfapExchange = a})
ppfapOverview :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapOverview
= lens _ppfapOverview
(\ s a -> s{_ppfapOverview = a})
ppfapGooglePlusLink :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapGooglePlusLink
= lens _ppfapGooglePlusLink
(\ s a -> s{_ppfapGooglePlusLink = a})
ppfapProFileId :: Lens' PublisherProFileAPIProto (Maybe Int32)
ppfapProFileId
= lens _ppfapProFileId
(\ s a -> s{_ppfapProFileId = a})
. mapping _Coerce
ppfapIsParent :: Lens' PublisherProFileAPIProto (Maybe Bool)
ppfapIsParent
= lens _ppfapIsParent
(\ s a -> s{_ppfapIsParent = a})
ppfapSeller :: Lens' PublisherProFileAPIProto (Maybe Seller)
ppfapSeller
= lens _ppfapSeller (\ s a -> s{_ppfapSeller = a})
ppfapAccountId :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapAccountId
= lens _ppfapAccountId
(\ s a -> s{_ppfapAccountId = a})
ppfapName :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapName
= lens _ppfapName (\ s a -> s{_ppfapName = a})
ppfapBuyerPitchStatement :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapBuyerPitchStatement
= lens _ppfapBuyerPitchStatement
(\ s a -> s{_ppfapBuyerPitchStatement = a})
ppfapPublisherProvidedForecast :: Lens' PublisherProFileAPIProto (Maybe PublisherProvidedForecast)
ppfapPublisherProvidedForecast
= lens _ppfapPublisherProvidedForecast
(\ s a -> s{_ppfapPublisherProvidedForecast = a})
ppfapIsPublished :: Lens' PublisherProFileAPIProto (Maybe Bool)
ppfapIsPublished
= lens _ppfapIsPublished
(\ s a -> s{_ppfapIsPublished = a})
ppfapPublisherDomains :: Lens' PublisherProFileAPIProto [Text]
ppfapPublisherDomains
= lens _ppfapPublisherDomains
(\ s a -> s{_ppfapPublisherDomains = a})
. _Default
. _Coerce
ppfapPublisherProFileId :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapPublisherProFileId
= lens _ppfapPublisherProFileId
(\ s a -> s{_ppfapPublisherProFileId = a})
ppfapRateCardInfoLink :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapRateCardInfoLink
= lens _ppfapRateCardInfoLink
(\ s a -> s{_ppfapRateCardInfoLink = a})
ppfapTopHeadlines :: Lens' PublisherProFileAPIProto [Text]
ppfapTopHeadlines
= lens _ppfapTopHeadlines
(\ s a -> s{_ppfapTopHeadlines = a})
. _Default
. _Coerce
ppfapProgrammaticContact :: Lens' PublisherProFileAPIProto (Maybe Text)
ppfapProgrammaticContact
= lens _ppfapProgrammaticContact
(\ s a -> s{_ppfapProgrammaticContact = a})
instance FromJSON PublisherProFileAPIProto where
parseJSON
= withObject "PublisherProFileAPIProto"
(\ o ->
PublisherProFileAPIProto' <$>
(o .:? "audience") <*> (o .:? "state") <*>
(o .:? "mediaKitLink")
<*> (o .:? "directContact")
<*> (o .:? "samplePageLink")
<*> (o .:? "logoUrl")
<*>
(o .:? "kind" .!=
"adexchangebuyer#publisherProfileApiProto")
<*> (o .:? "exchange")
<*> (o .:? "overview")
<*> (o .:? "googlePlusLink")
<*> (o .:? "profileId")
<*> (o .:? "isParent")
<*> (o .:? "seller")
<*> (o .:? "accountId")
<*> (o .:? "name")
<*> (o .:? "buyerPitchStatement")
<*> (o .:? "publisherProvidedForecast")
<*> (o .:? "isPublished")
<*> (o .:? "publisherDomains" .!= mempty)
<*> (o .:? "publisherProfileId")
<*> (o .:? "rateCardInfoLink")
<*> (o .:? "topHeadlines" .!= mempty)
<*> (o .:? "programmaticContact"))
instance ToJSON PublisherProFileAPIProto where
toJSON PublisherProFileAPIProto'{..}
= object
(catMaybes
[("audience" .=) <$> _ppfapAudience,
("state" .=) <$> _ppfapState,
("mediaKitLink" .=) <$> _ppfapMediaKitLink,
("directContact" .=) <$> _ppfapDirectContact,
("samplePageLink" .=) <$> _ppfapSamplePageLink,
("logoUrl" .=) <$> _ppfapLogoURL,
Just ("kind" .= _ppfapKind),
("exchange" .=) <$> _ppfapExchange,
("overview" .=) <$> _ppfapOverview,
("googlePlusLink" .=) <$> _ppfapGooglePlusLink,
("profileId" .=) <$> _ppfapProFileId,
("isParent" .=) <$> _ppfapIsParent,
("seller" .=) <$> _ppfapSeller,
("accountId" .=) <$> _ppfapAccountId,
("name" .=) <$> _ppfapName,
("buyerPitchStatement" .=) <$>
_ppfapBuyerPitchStatement,
("publisherProvidedForecast" .=) <$>
_ppfapPublisherProvidedForecast,
("isPublished" .=) <$> _ppfapIsPublished,
("publisherDomains" .=) <$> _ppfapPublisherDomains,
("publisherProfileId" .=) <$>
_ppfapPublisherProFileId,
("rateCardInfoLink" .=) <$> _ppfapRateCardInfoLink,
("topHeadlines" .=) <$> _ppfapTopHeadlines,
("programmaticContact" .=) <$>
_ppfapProgrammaticContact])
data MarketplaceDeal = MarketplaceDeal'
{ _mdExternalDealId :: !(Maybe Text)
, _mdBuyerPrivateData :: !(Maybe PrivateData)
, _mdWebPropertyCode :: !(Maybe Text)
, _mdCreationTimeMs :: !(Maybe (Textual Int64))
, _mdTerms :: !(Maybe DealTerms)
, _mdLastUpdateTimeMs :: !(Maybe (Textual Int64))
, _mdKind :: !Text
, _mdDeliveryControl :: !(Maybe DeliveryControl)
, _mdDealServingMetadata :: !(Maybe DealServingMetadata)
, _mdFlightStartTimeMs :: !(Maybe (Textual Int64))
, _mdSharedTargetings :: !(Maybe [SharedTargeting])
, _mdIsRfpTemplate :: !(Maybe Bool)
, _mdProposalId :: !(Maybe Text)
, _mdDealId :: !(Maybe Text)
, _mdInventoryDescription :: !(Maybe Text)
, _mdSyndicationProduct :: !(Maybe Text)
, _mdFlightEndTimeMs :: !(Maybe (Textual Int64))
, _mdName :: !(Maybe Text)
, _mdSellerContacts :: !(Maybe [ContactInformation])
, _mdProgrammaticCreativeSource :: !(Maybe Text)
, _mdCreativePreApprovalPolicy :: !(Maybe Text)
, _mdProductRevisionNumber :: !(Maybe (Textual Int64))
, _mdProductId :: !(Maybe Text)
, _mdCreativeSafeFrameCompatibility :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
marketplaceDeal
:: MarketplaceDeal
marketplaceDeal =
MarketplaceDeal'
{ _mdExternalDealId = Nothing
, _mdBuyerPrivateData = Nothing
, _mdWebPropertyCode = Nothing
, _mdCreationTimeMs = Nothing
, _mdTerms = Nothing
, _mdLastUpdateTimeMs = Nothing
, _mdKind = "adexchangebuyer#marketplaceDeal"
, _mdDeliveryControl = Nothing
, _mdDealServingMetadata = Nothing
, _mdFlightStartTimeMs = Nothing
, _mdSharedTargetings = Nothing
, _mdIsRfpTemplate = Nothing
, _mdProposalId = Nothing
, _mdDealId = Nothing
, _mdInventoryDescription = Nothing
, _mdSyndicationProduct = Nothing
, _mdFlightEndTimeMs = Nothing
, _mdName = Nothing
, _mdSellerContacts = Nothing
, _mdProgrammaticCreativeSource = Nothing
, _mdCreativePreApprovalPolicy = Nothing
, _mdProductRevisionNumber = Nothing
, _mdProductId = Nothing
, _mdCreativeSafeFrameCompatibility = Nothing
}
mdExternalDealId :: Lens' MarketplaceDeal (Maybe Text)
mdExternalDealId
= lens _mdExternalDealId
(\ s a -> s{_mdExternalDealId = a})
mdBuyerPrivateData :: Lens' MarketplaceDeal (Maybe PrivateData)
mdBuyerPrivateData
= lens _mdBuyerPrivateData
(\ s a -> s{_mdBuyerPrivateData = a})
mdWebPropertyCode :: Lens' MarketplaceDeal (Maybe Text)
mdWebPropertyCode
= lens _mdWebPropertyCode
(\ s a -> s{_mdWebPropertyCode = a})
mdCreationTimeMs :: Lens' MarketplaceDeal (Maybe Int64)
mdCreationTimeMs
= lens _mdCreationTimeMs
(\ s a -> s{_mdCreationTimeMs = a})
. mapping _Coerce
mdTerms :: Lens' MarketplaceDeal (Maybe DealTerms)
mdTerms = lens _mdTerms (\ s a -> s{_mdTerms = a})
mdLastUpdateTimeMs :: Lens' MarketplaceDeal (Maybe Int64)
mdLastUpdateTimeMs
= lens _mdLastUpdateTimeMs
(\ s a -> s{_mdLastUpdateTimeMs = a})
. mapping _Coerce
mdKind :: Lens' MarketplaceDeal Text
mdKind = lens _mdKind (\ s a -> s{_mdKind = a})
mdDeliveryControl :: Lens' MarketplaceDeal (Maybe DeliveryControl)
mdDeliveryControl
= lens _mdDeliveryControl
(\ s a -> s{_mdDeliveryControl = a})
mdDealServingMetadata :: Lens' MarketplaceDeal (Maybe DealServingMetadata)
mdDealServingMetadata
= lens _mdDealServingMetadata
(\ s a -> s{_mdDealServingMetadata = a})
mdFlightStartTimeMs :: Lens' MarketplaceDeal (Maybe Int64)
mdFlightStartTimeMs
= lens _mdFlightStartTimeMs
(\ s a -> s{_mdFlightStartTimeMs = a})
. mapping _Coerce
mdSharedTargetings :: Lens' MarketplaceDeal [SharedTargeting]
mdSharedTargetings
= lens _mdSharedTargetings
(\ s a -> s{_mdSharedTargetings = a})
. _Default
. _Coerce
mdIsRfpTemplate :: Lens' MarketplaceDeal (Maybe Bool)
mdIsRfpTemplate
= lens _mdIsRfpTemplate
(\ s a -> s{_mdIsRfpTemplate = a})
mdProposalId :: Lens' MarketplaceDeal (Maybe Text)
mdProposalId
= lens _mdProposalId (\ s a -> s{_mdProposalId = a})
mdDealId :: Lens' MarketplaceDeal (Maybe Text)
mdDealId = lens _mdDealId (\ s a -> s{_mdDealId = a})
mdInventoryDescription :: Lens' MarketplaceDeal (Maybe Text)
mdInventoryDescription
= lens _mdInventoryDescription
(\ s a -> s{_mdInventoryDescription = a})
mdSyndicationProduct :: Lens' MarketplaceDeal (Maybe Text)
mdSyndicationProduct
= lens _mdSyndicationProduct
(\ s a -> s{_mdSyndicationProduct = a})
mdFlightEndTimeMs :: Lens' MarketplaceDeal (Maybe Int64)
mdFlightEndTimeMs
= lens _mdFlightEndTimeMs
(\ s a -> s{_mdFlightEndTimeMs = a})
. mapping _Coerce
mdName :: Lens' MarketplaceDeal (Maybe Text)
mdName = lens _mdName (\ s a -> s{_mdName = a})
mdSellerContacts :: Lens' MarketplaceDeal [ContactInformation]
mdSellerContacts
= lens _mdSellerContacts
(\ s a -> s{_mdSellerContacts = a})
. _Default
. _Coerce
mdProgrammaticCreativeSource :: Lens' MarketplaceDeal (Maybe Text)
mdProgrammaticCreativeSource
= lens _mdProgrammaticCreativeSource
(\ s a -> s{_mdProgrammaticCreativeSource = a})
mdCreativePreApprovalPolicy :: Lens' MarketplaceDeal (Maybe Text)
mdCreativePreApprovalPolicy
= lens _mdCreativePreApprovalPolicy
(\ s a -> s{_mdCreativePreApprovalPolicy = a})
mdProductRevisionNumber :: Lens' MarketplaceDeal (Maybe Int64)
mdProductRevisionNumber
= lens _mdProductRevisionNumber
(\ s a -> s{_mdProductRevisionNumber = a})
. mapping _Coerce
mdProductId :: Lens' MarketplaceDeal (Maybe Text)
mdProductId
= lens _mdProductId (\ s a -> s{_mdProductId = a})
mdCreativeSafeFrameCompatibility :: Lens' MarketplaceDeal (Maybe Text)
mdCreativeSafeFrameCompatibility
= lens _mdCreativeSafeFrameCompatibility
(\ s a -> s{_mdCreativeSafeFrameCompatibility = a})
instance FromJSON MarketplaceDeal where
parseJSON
= withObject "MarketplaceDeal"
(\ o ->
MarketplaceDeal' <$>
(o .:? "externalDealId") <*>
(o .:? "buyerPrivateData")
<*> (o .:? "webPropertyCode")
<*> (o .:? "creationTimeMs")
<*> (o .:? "terms")
<*> (o .:? "lastUpdateTimeMs")
<*>
(o .:? "kind" .!= "adexchangebuyer#marketplaceDeal")
<*> (o .:? "deliveryControl")
<*> (o .:? "dealServingMetadata")
<*> (o .:? "flightStartTimeMs")
<*> (o .:? "sharedTargetings" .!= mempty)
<*> (o .:? "isRfpTemplate")
<*> (o .:? "proposalId")
<*> (o .:? "dealId")
<*> (o .:? "inventoryDescription")
<*> (o .:? "syndicationProduct")
<*> (o .:? "flightEndTimeMs")
<*> (o .:? "name")
<*> (o .:? "sellerContacts" .!= mempty)
<*> (o .:? "programmaticCreativeSource")
<*> (o .:? "creativePreApprovalPolicy")
<*> (o .:? "productRevisionNumber")
<*> (o .:? "productId")
<*> (o .:? "creativeSafeFrameCompatibility"))
instance ToJSON MarketplaceDeal where
toJSON MarketplaceDeal'{..}
= object
(catMaybes
[("externalDealId" .=) <$> _mdExternalDealId,
("buyerPrivateData" .=) <$> _mdBuyerPrivateData,
("webPropertyCode" .=) <$> _mdWebPropertyCode,
("creationTimeMs" .=) <$> _mdCreationTimeMs,
("terms" .=) <$> _mdTerms,
("lastUpdateTimeMs" .=) <$> _mdLastUpdateTimeMs,
Just ("kind" .= _mdKind),
("deliveryControl" .=) <$> _mdDeliveryControl,
("dealServingMetadata" .=) <$>
_mdDealServingMetadata,
("flightStartTimeMs" .=) <$> _mdFlightStartTimeMs,
("sharedTargetings" .=) <$> _mdSharedTargetings,
("isRfpTemplate" .=) <$> _mdIsRfpTemplate,
("proposalId" .=) <$> _mdProposalId,
("dealId" .=) <$> _mdDealId,
("inventoryDescription" .=) <$>
_mdInventoryDescription,
("syndicationProduct" .=) <$> _mdSyndicationProduct,
("flightEndTimeMs" .=) <$> _mdFlightEndTimeMs,
("name" .=) <$> _mdName,
("sellerContacts" .=) <$> _mdSellerContacts,
("programmaticCreativeSource" .=) <$>
_mdProgrammaticCreativeSource,
("creativePreApprovalPolicy" .=) <$>
_mdCreativePreApprovalPolicy,
("productRevisionNumber" .=) <$>
_mdProductRevisionNumber,
("productId" .=) <$> _mdProductId,
("creativeSafeFrameCompatibility" .=) <$>
_mdCreativeSafeFrameCompatibility])
newtype GetOffersResponse = GetOffersResponse'
{ _gorProducts :: Maybe [Product]
} deriving (Eq,Show,Data,Typeable,Generic)
getOffersResponse
:: GetOffersResponse
getOffersResponse =
GetOffersResponse'
{ _gorProducts = Nothing
}
gorProducts :: Lens' GetOffersResponse [Product]
gorProducts
= lens _gorProducts (\ s a -> s{_gorProducts = a}) .
_Default
. _Coerce
instance FromJSON GetOffersResponse where
parseJSON
= withObject "GetOffersResponse"
(\ o ->
GetOffersResponse' <$> (o .:? "products" .!= mempty))
instance ToJSON GetOffersResponse where
toJSON GetOffersResponse'{..}
= object
(catMaybes [("products" .=) <$> _gorProducts])
data DealTermsNonGuaranteedAuctionTerms = DealTermsNonGuaranteedAuctionTerms'
{ _dtngatReservePricePerBuyers :: !(Maybe [PricePerBuyer])
, _dtngatAutoOptimizePrivateAuction :: !(Maybe Bool)
} deriving (Eq,Show,Data,Typeable,Generic)
dealTermsNonGuaranteedAuctionTerms
:: DealTermsNonGuaranteedAuctionTerms
dealTermsNonGuaranteedAuctionTerms =
DealTermsNonGuaranteedAuctionTerms'
{ _dtngatReservePricePerBuyers = Nothing
, _dtngatAutoOptimizePrivateAuction = Nothing
}
dtngatReservePricePerBuyers :: Lens' DealTermsNonGuaranteedAuctionTerms [PricePerBuyer]
dtngatReservePricePerBuyers
= lens _dtngatReservePricePerBuyers
(\ s a -> s{_dtngatReservePricePerBuyers = a})
. _Default
. _Coerce
dtngatAutoOptimizePrivateAuction :: Lens' DealTermsNonGuaranteedAuctionTerms (Maybe Bool)
dtngatAutoOptimizePrivateAuction
= lens _dtngatAutoOptimizePrivateAuction
(\ s a -> s{_dtngatAutoOptimizePrivateAuction = a})
instance FromJSON DealTermsNonGuaranteedAuctionTerms
where
parseJSON
= withObject "DealTermsNonGuaranteedAuctionTerms"
(\ o ->
DealTermsNonGuaranteedAuctionTerms' <$>
(o .:? "reservePricePerBuyers" .!= mempty) <*>
(o .:? "autoOptimizePrivateAuction"))
instance ToJSON DealTermsNonGuaranteedAuctionTerms
where
toJSON DealTermsNonGuaranteedAuctionTerms'{..}
= object
(catMaybes
[("reservePricePerBuyers" .=) <$>
_dtngatReservePricePerBuyers,
("autoOptimizePrivateAuction" .=) <$>
_dtngatAutoOptimizePrivateAuction])
data CreativeFilteringReasonsReasonsItem = CreativeFilteringReasonsReasonsItem'
{ _cfrriFilteringStatus :: !(Maybe (Textual Int32))
, _cfrriFilteringCount :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
creativeFilteringReasonsReasonsItem
:: CreativeFilteringReasonsReasonsItem
creativeFilteringReasonsReasonsItem =
CreativeFilteringReasonsReasonsItem'
{ _cfrriFilteringStatus = Nothing
, _cfrriFilteringCount = Nothing
}
cfrriFilteringStatus :: Lens' CreativeFilteringReasonsReasonsItem (Maybe Int32)
cfrriFilteringStatus
= lens _cfrriFilteringStatus
(\ s a -> s{_cfrriFilteringStatus = a})
. mapping _Coerce
cfrriFilteringCount :: Lens' CreativeFilteringReasonsReasonsItem (Maybe Int64)
cfrriFilteringCount
= lens _cfrriFilteringCount
(\ s a -> s{_cfrriFilteringCount = a})
. mapping _Coerce
instance FromJSON CreativeFilteringReasonsReasonsItem
where
parseJSON
= withObject "CreativeFilteringReasonsReasonsItem"
(\ o ->
CreativeFilteringReasonsReasonsItem' <$>
(o .:? "filteringStatus") <*>
(o .:? "filteringCount"))
instance ToJSON CreativeFilteringReasonsReasonsItem
where
toJSON CreativeFilteringReasonsReasonsItem'{..}
= object
(catMaybes
[("filteringStatus" .=) <$> _cfrriFilteringStatus,
("filteringCount" .=) <$> _cfrriFilteringCount])
data DealTerms = DealTerms'
{ _dtEstimatedGrossSpend :: !(Maybe Price)
, _dtNonGuaranteedFixedPriceTerms :: !(Maybe DealTermsNonGuaranteedFixedPriceTerms)
, _dtNonGuaranteedAuctionTerms :: !(Maybe DealTermsNonGuaranteedAuctionTerms)
, _dtRubiconNonGuaranteedTerms :: !(Maybe DealTermsRubiconNonGuaranteedTerms)
, _dtBrandingType :: !(Maybe Text)
, _dtCrossListedExternalDealIdType :: !(Maybe Text)
, _dtEstimatedImpressionsPerDay :: !(Maybe (Textual Int64))
, _dtSellerTimeZone :: !(Maybe Text)
, _dtGuaranteedFixedPriceTerms :: !(Maybe DealTermsGuaranteedFixedPriceTerms)
, _dtDescription :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
dealTerms
:: DealTerms
dealTerms =
DealTerms'
{ _dtEstimatedGrossSpend = Nothing
, _dtNonGuaranteedFixedPriceTerms = Nothing
, _dtNonGuaranteedAuctionTerms = Nothing
, _dtRubiconNonGuaranteedTerms = Nothing
, _dtBrandingType = Nothing
, _dtCrossListedExternalDealIdType = Nothing
, _dtEstimatedImpressionsPerDay = Nothing
, _dtSellerTimeZone = Nothing
, _dtGuaranteedFixedPriceTerms = Nothing
, _dtDescription = Nothing
}
dtEstimatedGrossSpend :: Lens' DealTerms (Maybe Price)
dtEstimatedGrossSpend
= lens _dtEstimatedGrossSpend
(\ s a -> s{_dtEstimatedGrossSpend = a})
dtNonGuaranteedFixedPriceTerms :: Lens' DealTerms (Maybe DealTermsNonGuaranteedFixedPriceTerms)
dtNonGuaranteedFixedPriceTerms
= lens _dtNonGuaranteedFixedPriceTerms
(\ s a -> s{_dtNonGuaranteedFixedPriceTerms = a})
dtNonGuaranteedAuctionTerms :: Lens' DealTerms (Maybe DealTermsNonGuaranteedAuctionTerms)
dtNonGuaranteedAuctionTerms
= lens _dtNonGuaranteedAuctionTerms
(\ s a -> s{_dtNonGuaranteedAuctionTerms = a})
dtRubiconNonGuaranteedTerms :: Lens' DealTerms (Maybe DealTermsRubiconNonGuaranteedTerms)
dtRubiconNonGuaranteedTerms
= lens _dtRubiconNonGuaranteedTerms
(\ s a -> s{_dtRubiconNonGuaranteedTerms = a})
dtBrandingType :: Lens' DealTerms (Maybe Text)
dtBrandingType
= lens _dtBrandingType
(\ s a -> s{_dtBrandingType = a})
dtCrossListedExternalDealIdType :: Lens' DealTerms (Maybe Text)
dtCrossListedExternalDealIdType
= lens _dtCrossListedExternalDealIdType
(\ s a -> s{_dtCrossListedExternalDealIdType = a})
dtEstimatedImpressionsPerDay :: Lens' DealTerms (Maybe Int64)
dtEstimatedImpressionsPerDay
= lens _dtEstimatedImpressionsPerDay
(\ s a -> s{_dtEstimatedImpressionsPerDay = a})
. mapping _Coerce
dtSellerTimeZone :: Lens' DealTerms (Maybe Text)
dtSellerTimeZone
= lens _dtSellerTimeZone
(\ s a -> s{_dtSellerTimeZone = a})
dtGuaranteedFixedPriceTerms :: Lens' DealTerms (Maybe DealTermsGuaranteedFixedPriceTerms)
dtGuaranteedFixedPriceTerms
= lens _dtGuaranteedFixedPriceTerms
(\ s a -> s{_dtGuaranteedFixedPriceTerms = a})
dtDescription :: Lens' DealTerms (Maybe Text)
dtDescription
= lens _dtDescription
(\ s a -> s{_dtDescription = a})
instance FromJSON DealTerms where
parseJSON
= withObject "DealTerms"
(\ o ->
DealTerms' <$>
(o .:? "estimatedGrossSpend") <*>
(o .:? "nonGuaranteedFixedPriceTerms")
<*> (o .:? "nonGuaranteedAuctionTerms")
<*> (o .:? "rubiconNonGuaranteedTerms")
<*> (o .:? "brandingType")
<*> (o .:? "crossListedExternalDealIdType")
<*> (o .:? "estimatedImpressionsPerDay")
<*> (o .:? "sellerTimeZone")
<*> (o .:? "guaranteedFixedPriceTerms")
<*> (o .:? "description"))
instance ToJSON DealTerms where
toJSON DealTerms'{..}
= object
(catMaybes
[("estimatedGrossSpend" .=) <$>
_dtEstimatedGrossSpend,
("nonGuaranteedFixedPriceTerms" .=) <$>
_dtNonGuaranteedFixedPriceTerms,
("nonGuaranteedAuctionTerms" .=) <$>
_dtNonGuaranteedAuctionTerms,
("rubiconNonGuaranteedTerms" .=) <$>
_dtRubiconNonGuaranteedTerms,
("brandingType" .=) <$> _dtBrandingType,
("crossListedExternalDealIdType" .=) <$>
_dtCrossListedExternalDealIdType,
("estimatedImpressionsPerDay" .=) <$>
_dtEstimatedImpressionsPerDay,
("sellerTimeZone" .=) <$> _dtSellerTimeZone,
("guaranteedFixedPriceTerms" .=) <$>
_dtGuaranteedFixedPriceTerms,
("description" .=) <$> _dtDescription])
data CreativeDealIds = CreativeDealIds'
{ _cdiKind :: !Text
, _cdiDealStatuses :: !(Maybe [CreativeDealIdsDealStatusesItem])
} deriving (Eq,Show,Data,Typeable,Generic)
creativeDealIds
:: CreativeDealIds
creativeDealIds =
CreativeDealIds'
{ _cdiKind = "adexchangebuyer#creativeDealIds"
, _cdiDealStatuses = Nothing
}
cdiKind :: Lens' CreativeDealIds Text
cdiKind = lens _cdiKind (\ s a -> s{_cdiKind = a})
cdiDealStatuses :: Lens' CreativeDealIds [CreativeDealIdsDealStatusesItem]
cdiDealStatuses
= lens _cdiDealStatuses
(\ s a -> s{_cdiDealStatuses = a})
. _Default
. _Coerce
instance FromJSON CreativeDealIds where
parseJSON
= withObject "CreativeDealIds"
(\ o ->
CreativeDealIds' <$>
(o .:? "kind" .!= "adexchangebuyer#creativeDealIds")
<*> (o .:? "dealStatuses" .!= mempty))
instance ToJSON CreativeDealIds where
toJSON CreativeDealIds'{..}
= object
(catMaybes
[Just ("kind" .= _cdiKind),
("dealStatuses" .=) <$> _cdiDealStatuses])
data MarketplaceLabel = MarketplaceLabel'
{ _mlDeprecatedMarketplaceDealParty :: !(Maybe MarketplaceDealParty)
, _mlAccountId :: !(Maybe Text)
, _mlCreateTimeMs :: !(Maybe (Textual Int64))
, _mlLabel :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
marketplaceLabel
:: MarketplaceLabel
marketplaceLabel =
MarketplaceLabel'
{ _mlDeprecatedMarketplaceDealParty = Nothing
, _mlAccountId = Nothing
, _mlCreateTimeMs = Nothing
, _mlLabel = Nothing
}
mlDeprecatedMarketplaceDealParty :: Lens' MarketplaceLabel (Maybe MarketplaceDealParty)
mlDeprecatedMarketplaceDealParty
= lens _mlDeprecatedMarketplaceDealParty
(\ s a -> s{_mlDeprecatedMarketplaceDealParty = a})
mlAccountId :: Lens' MarketplaceLabel (Maybe Text)
mlAccountId
= lens _mlAccountId (\ s a -> s{_mlAccountId = a})
mlCreateTimeMs :: Lens' MarketplaceLabel (Maybe Int64)
mlCreateTimeMs
= lens _mlCreateTimeMs
(\ s a -> s{_mlCreateTimeMs = a})
. mapping _Coerce
mlLabel :: Lens' MarketplaceLabel (Maybe Text)
mlLabel = lens _mlLabel (\ s a -> s{_mlLabel = a})
instance FromJSON MarketplaceLabel where
parseJSON
= withObject "MarketplaceLabel"
(\ o ->
MarketplaceLabel' <$>
(o .:? "deprecatedMarketplaceDealParty") <*>
(o .:? "accountId")
<*> (o .:? "createTimeMs")
<*> (o .:? "label"))
instance ToJSON MarketplaceLabel where
toJSON MarketplaceLabel'{..}
= object
(catMaybes
[("deprecatedMarketplaceDealParty" .=) <$>
_mlDeprecatedMarketplaceDealParty,
("accountId" .=) <$> _mlAccountId,
("createTimeMs" .=) <$> _mlCreateTimeMs,
("label" .=) <$> _mlLabel])
newtype Buyer = Buyer'
{ _buyAccountId :: Maybe Text
} deriving (Eq,Show,Data,Typeable,Generic)
buyer
:: Buyer
buyer =
Buyer'
{ _buyAccountId = Nothing
}
buyAccountId :: Lens' Buyer (Maybe Text)
buyAccountId
= lens _buyAccountId (\ s a -> s{_buyAccountId = a})
instance FromJSON Buyer where
parseJSON
= withObject "Buyer"
(\ o -> Buyer' <$> (o .:? "accountId"))
instance ToJSON Buyer where
toJSON Buyer'{..}
= object
(catMaybes [("accountId" .=) <$> _buyAccountId])
data AddOrderDealsRequest = AddOrderDealsRequest'
{ _aUpdateAction :: !(Maybe Text)
, _aDeals :: !(Maybe [MarketplaceDeal])
, _aProposalRevisionNumber :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
addOrderDealsRequest
:: AddOrderDealsRequest
addOrderDealsRequest =
AddOrderDealsRequest'
{ _aUpdateAction = Nothing
, _aDeals = Nothing
, _aProposalRevisionNumber = Nothing
}
aUpdateAction :: Lens' AddOrderDealsRequest (Maybe Text)
aUpdateAction
= lens _aUpdateAction
(\ s a -> s{_aUpdateAction = a})
aDeals :: Lens' AddOrderDealsRequest [MarketplaceDeal]
aDeals
= lens _aDeals (\ s a -> s{_aDeals = a}) . _Default .
_Coerce
aProposalRevisionNumber :: Lens' AddOrderDealsRequest (Maybe Int64)
aProposalRevisionNumber
= lens _aProposalRevisionNumber
(\ s a -> s{_aProposalRevisionNumber = a})
. mapping _Coerce
instance FromJSON AddOrderDealsRequest where
parseJSON
= withObject "AddOrderDealsRequest"
(\ o ->
AddOrderDealsRequest' <$>
(o .:? "updateAction") <*> (o .:? "deals" .!= mempty)
<*> (o .:? "proposalRevisionNumber"))
instance ToJSON AddOrderDealsRequest where
toJSON AddOrderDealsRequest'{..}
= object
(catMaybes
[("updateAction" .=) <$> _aUpdateAction,
("deals" .=) <$> _aDeals,
("proposalRevisionNumber" .=) <$>
_aProposalRevisionNumber])
data DealServingMetadataDealPauseStatus = DealServingMetadataDealPauseStatus'
{ _dsmdpsFirstPausedBy :: !(Maybe Text)
, _dsmdpsBuyerPauseReason :: !(Maybe Text)
, _dsmdpsHasBuyerPaused :: !(Maybe Bool)
, _dsmdpsSellerPauseReason :: !(Maybe Text)
, _dsmdpsHasSellerPaused :: !(Maybe Bool)
} deriving (Eq,Show,Data,Typeable,Generic)
dealServingMetadataDealPauseStatus
:: DealServingMetadataDealPauseStatus
dealServingMetadataDealPauseStatus =
DealServingMetadataDealPauseStatus'
{ _dsmdpsFirstPausedBy = Nothing
, _dsmdpsBuyerPauseReason = Nothing
, _dsmdpsHasBuyerPaused = Nothing
, _dsmdpsSellerPauseReason = Nothing
, _dsmdpsHasSellerPaused = Nothing
}
dsmdpsFirstPausedBy :: Lens' DealServingMetadataDealPauseStatus (Maybe Text)
dsmdpsFirstPausedBy
= lens _dsmdpsFirstPausedBy
(\ s a -> s{_dsmdpsFirstPausedBy = a})
dsmdpsBuyerPauseReason :: Lens' DealServingMetadataDealPauseStatus (Maybe Text)
dsmdpsBuyerPauseReason
= lens _dsmdpsBuyerPauseReason
(\ s a -> s{_dsmdpsBuyerPauseReason = a})
dsmdpsHasBuyerPaused :: Lens' DealServingMetadataDealPauseStatus (Maybe Bool)
dsmdpsHasBuyerPaused
= lens _dsmdpsHasBuyerPaused
(\ s a -> s{_dsmdpsHasBuyerPaused = a})
dsmdpsSellerPauseReason :: Lens' DealServingMetadataDealPauseStatus (Maybe Text)
dsmdpsSellerPauseReason
= lens _dsmdpsSellerPauseReason
(\ s a -> s{_dsmdpsSellerPauseReason = a})
dsmdpsHasSellerPaused :: Lens' DealServingMetadataDealPauseStatus (Maybe Bool)
dsmdpsHasSellerPaused
= lens _dsmdpsHasSellerPaused
(\ s a -> s{_dsmdpsHasSellerPaused = a})
instance FromJSON DealServingMetadataDealPauseStatus
where
parseJSON
= withObject "DealServingMetadataDealPauseStatus"
(\ o ->
DealServingMetadataDealPauseStatus' <$>
(o .:? "firstPausedBy") <*>
(o .:? "buyerPauseReason")
<*> (o .:? "hasBuyerPaused")
<*> (o .:? "sellerPauseReason")
<*> (o .:? "hasSellerPaused"))
instance ToJSON DealServingMetadataDealPauseStatus
where
toJSON DealServingMetadataDealPauseStatus'{..}
= object
(catMaybes
[("firstPausedBy" .=) <$> _dsmdpsFirstPausedBy,
("buyerPauseReason" .=) <$> _dsmdpsBuyerPauseReason,
("hasBuyerPaused" .=) <$> _dsmdpsHasBuyerPaused,
("sellerPauseReason" .=) <$>
_dsmdpsSellerPauseReason,
("hasSellerPaused" .=) <$> _dsmdpsHasSellerPaused])
data DealTermsGuaranteedFixedPriceTerms = DealTermsGuaranteedFixedPriceTerms'
{ _dtgfptGuaranteedLooks :: !(Maybe (Textual Int64))
, _dtgfptGuaranteedImpressions :: !(Maybe (Textual Int64))
, _dtgfptBillingInfo :: !(Maybe DealTermsGuaranteedFixedPriceTermsBillingInfo)
, _dtgfptFixedPrices :: !(Maybe [PricePerBuyer])
, _dtgfptMinimumDailyLooks :: !(Maybe (Textual Int64))
} deriving (Eq,Show,Data,Typeable,Generic)
dealTermsGuaranteedFixedPriceTerms
:: DealTermsGuaranteedFixedPriceTerms
dealTermsGuaranteedFixedPriceTerms =
DealTermsGuaranteedFixedPriceTerms'
{ _dtgfptGuaranteedLooks = Nothing
, _dtgfptGuaranteedImpressions = Nothing
, _dtgfptBillingInfo = Nothing
, _dtgfptFixedPrices = Nothing
, _dtgfptMinimumDailyLooks = Nothing
}
dtgfptGuaranteedLooks :: Lens' DealTermsGuaranteedFixedPriceTerms (Maybe Int64)
dtgfptGuaranteedLooks
= lens _dtgfptGuaranteedLooks
(\ s a -> s{_dtgfptGuaranteedLooks = a})
. mapping _Coerce
dtgfptGuaranteedImpressions :: Lens' DealTermsGuaranteedFixedPriceTerms (Maybe Int64)
dtgfptGuaranteedImpressions
= lens _dtgfptGuaranteedImpressions
(\ s a -> s{_dtgfptGuaranteedImpressions = a})
. mapping _Coerce
dtgfptBillingInfo :: Lens' DealTermsGuaranteedFixedPriceTerms (Maybe DealTermsGuaranteedFixedPriceTermsBillingInfo)
dtgfptBillingInfo
= lens _dtgfptBillingInfo
(\ s a -> s{_dtgfptBillingInfo = a})
dtgfptFixedPrices :: Lens' DealTermsGuaranteedFixedPriceTerms [PricePerBuyer]
dtgfptFixedPrices
= lens _dtgfptFixedPrices
(\ s a -> s{_dtgfptFixedPrices = a})
. _Default
. _Coerce
dtgfptMinimumDailyLooks :: Lens' DealTermsGuaranteedFixedPriceTerms (Maybe Int64)
dtgfptMinimumDailyLooks
= lens _dtgfptMinimumDailyLooks
(\ s a -> s{_dtgfptMinimumDailyLooks = a})
. mapping _Coerce
instance FromJSON DealTermsGuaranteedFixedPriceTerms
where
parseJSON
= withObject "DealTermsGuaranteedFixedPriceTerms"
(\ o ->
DealTermsGuaranteedFixedPriceTerms' <$>
(o .:? "guaranteedLooks") <*>
(o .:? "guaranteedImpressions")
<*> (o .:? "billingInfo")
<*> (o .:? "fixedPrices" .!= mempty)
<*> (o .:? "minimumDailyLooks"))
instance ToJSON DealTermsGuaranteedFixedPriceTerms
where
toJSON DealTermsGuaranteedFixedPriceTerms'{..}
= object
(catMaybes
[("guaranteedLooks" .=) <$> _dtgfptGuaranteedLooks,
("guaranteedImpressions" .=) <$>
_dtgfptGuaranteedImpressions,
("billingInfo" .=) <$> _dtgfptBillingInfo,
("fixedPrices" .=) <$> _dtgfptFixedPrices,
("minimumDailyLooks" .=) <$>
_dtgfptMinimumDailyLooks])