{-# 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.Analytics.Data.Ga.Get
(
DataGaGetResource
, dataGaGet
, DataGaGet
, dggMetrics
, dggSamplingLevel
, dggFilters
, dggIds
, dggEndDate
, dggOutput
, dggSort
, dggIncludeEmptyRows
, dggDimensions
, dggStartIndex
, dggMaxResults
, dggSegment
, dggStartDate
) where
import Network.Google.Analytics.Types
import Network.Google.Prelude
type DataGaGetResource =
"analytics" :>
"v3" :>
"data" :>
"ga" :>
QueryParam "ids" Text :>
QueryParam "start-date" Text :>
QueryParam "end-date" Text :>
QueryParam "metrics" Text :>
QueryParam "samplingLevel" DataGaGetSamplingLevel :>
QueryParam "filters" Text :>
QueryParam "output" DataGaGetOutput :>
QueryParam "sort" Text :>
QueryParam "include-empty-rows" Bool :>
QueryParam "dimensions" Text :>
QueryParam "start-index" (Textual Int32) :>
QueryParam "max-results" (Textual Int32) :>
QueryParam "segment" Text :>
QueryParam "alt" AltJSON :>
Get '[JSON] GaData
data DataGaGet = DataGaGet'
{ _dggMetrics :: !Text
, _dggSamplingLevel :: !(Maybe DataGaGetSamplingLevel)
, _dggFilters :: !(Maybe Text)
, _dggIds :: !Text
, _dggEndDate :: !Text
, _dggOutput :: !(Maybe DataGaGetOutput)
, _dggSort :: !(Maybe Text)
, _dggIncludeEmptyRows :: !(Maybe Bool)
, _dggDimensions :: !(Maybe Text)
, _dggStartIndex :: !(Maybe (Textual Int32))
, _dggMaxResults :: !(Maybe (Textual Int32))
, _dggSegment :: !(Maybe Text)
, _dggStartDate :: !Text
} deriving (Eq,Show,Data,Typeable,Generic)
dataGaGet
:: Text
-> Text
-> Text
-> Text
-> DataGaGet
dataGaGet pDggMetrics_ pDggIds_ pDggEndDate_ pDggStartDate_ =
DataGaGet'
{ _dggMetrics = pDggMetrics_
, _dggSamplingLevel = Nothing
, _dggFilters = Nothing
, _dggIds = pDggIds_
, _dggEndDate = pDggEndDate_
, _dggOutput = Nothing
, _dggSort = Nothing
, _dggIncludeEmptyRows = Nothing
, _dggDimensions = Nothing
, _dggStartIndex = Nothing
, _dggMaxResults = Nothing
, _dggSegment = Nothing
, _dggStartDate = pDggStartDate_
}
dggMetrics :: Lens' DataGaGet Text
dggMetrics
= lens _dggMetrics (\ s a -> s{_dggMetrics = a})
dggSamplingLevel :: Lens' DataGaGet (Maybe DataGaGetSamplingLevel)
dggSamplingLevel
= lens _dggSamplingLevel
(\ s a -> s{_dggSamplingLevel = a})
dggFilters :: Lens' DataGaGet (Maybe Text)
dggFilters
= lens _dggFilters (\ s a -> s{_dggFilters = a})
dggIds :: Lens' DataGaGet Text
dggIds = lens _dggIds (\ s a -> s{_dggIds = a})
dggEndDate :: Lens' DataGaGet Text
dggEndDate
= lens _dggEndDate (\ s a -> s{_dggEndDate = a})
dggOutput :: Lens' DataGaGet (Maybe DataGaGetOutput)
dggOutput
= lens _dggOutput (\ s a -> s{_dggOutput = a})
dggSort :: Lens' DataGaGet (Maybe Text)
dggSort = lens _dggSort (\ s a -> s{_dggSort = a})
dggIncludeEmptyRows :: Lens' DataGaGet (Maybe Bool)
dggIncludeEmptyRows
= lens _dggIncludeEmptyRows
(\ s a -> s{_dggIncludeEmptyRows = a})
dggDimensions :: Lens' DataGaGet (Maybe Text)
dggDimensions
= lens _dggDimensions
(\ s a -> s{_dggDimensions = a})
dggStartIndex :: Lens' DataGaGet (Maybe Int32)
dggStartIndex
= lens _dggStartIndex
(\ s a -> s{_dggStartIndex = a})
. mapping _Coerce
dggMaxResults :: Lens' DataGaGet (Maybe Int32)
dggMaxResults
= lens _dggMaxResults
(\ s a -> s{_dggMaxResults = a})
. mapping _Coerce
dggSegment :: Lens' DataGaGet (Maybe Text)
dggSegment
= lens _dggSegment (\ s a -> s{_dggSegment = a})
dggStartDate :: Lens' DataGaGet Text
dggStartDate
= lens _dggStartDate (\ s a -> s{_dggStartDate = a})
instance GoogleRequest DataGaGet where
type Rs DataGaGet = GaData
type Scopes DataGaGet =
'["https://www.googleapis.com/auth/analytics",
"https://www.googleapis.com/auth/analytics.readonly"]
requestClient DataGaGet'{..}
= go (Just _dggIds) (Just _dggStartDate)
(Just _dggEndDate)
(Just _dggMetrics)
_dggSamplingLevel
_dggFilters
_dggOutput
_dggSort
_dggIncludeEmptyRows
_dggDimensions
_dggStartIndex
_dggMaxResults
_dggSegment
(Just AltJSON)
analyticsService
where go
= buildClient (Proxy :: Proxy DataGaGetResource)
mempty