{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.Google.Resource.DoubleClickSearch.Reports.GetFile
(
ReportsGetFileResource
, reportsGetFile
, ReportsGetFile
, rgfReportId
, rgfReportFragment
) where
import Network.Google.DoubleClickSearch.Types
import Network.Google.Prelude
type ReportsGetFileResource =
"doubleclicksearch" :>
"v2" :>
"reports" :>
Capture "reportId" Text :>
"files" :>
Capture "reportFragment" (Textual Int32) :>
QueryParam "alt" AltJSON :> Get '[JSON] ()
:<|>
"doubleclicksearch" :>
"v2" :>
"reports" :>
Capture "reportId" Text :>
"files" :>
Capture "reportFragment" (Textual Int32) :>
QueryParam "alt" AltMedia :>
Get '[OctetStream] Stream
data ReportsGetFile = ReportsGetFile'
{ _rgfReportId :: !Text
, _rgfReportFragment :: !(Textual Int32)
} deriving (Eq,Show,Data,Typeable,Generic)
reportsGetFile
:: Text
-> Int32
-> ReportsGetFile
reportsGetFile pRgfReportId_ pRgfReportFragment_ =
ReportsGetFile'
{ _rgfReportId = pRgfReportId_
, _rgfReportFragment = _Coerce # pRgfReportFragment_
}
rgfReportId :: Lens' ReportsGetFile Text
rgfReportId
= lens _rgfReportId (\ s a -> s{_rgfReportId = a})
rgfReportFragment :: Lens' ReportsGetFile Int32
rgfReportFragment
= lens _rgfReportFragment
(\ s a -> s{_rgfReportFragment = a})
. _Coerce
instance GoogleRequest ReportsGetFile where
type Rs ReportsGetFile = ()
type Scopes ReportsGetFile =
'["https://www.googleapis.com/auth/doubleclicksearch"]
requestClient ReportsGetFile'{..}
= go _rgfReportId _rgfReportFragment (Just AltJSON)
doubleClickSearchService
where go :<|> _
= buildClient (Proxy :: Proxy ReportsGetFileResource)
mempty
instance GoogleRequest (MediaDownload ReportsGetFile)
where
type Rs (MediaDownload ReportsGetFile) = Stream
type Scopes (MediaDownload ReportsGetFile) =
Scopes ReportsGetFile
requestClient (MediaDownload ReportsGetFile'{..})
= go _rgfReportId _rgfReportFragment (Just AltMedia)
doubleClickSearchService
where _ :<|> go
= buildClient (Proxy :: Proxy ReportsGetFileResource)
mempty