gogol-admin-reports-0.5.0: Google Admin Reports SDK.

Copyright(c) 2015-2016 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.Google.Reports.Types

Contents

Description

 
Synopsis

Service Configuration

reportsService :: ServiceConfig Source #

Default request referring to version reports_v1 of the Admin Reports API. This contains the host and root path used as a starting point for constructing service requests.

OAuth Scopes

adminReportsUsageReadOnlyScope :: Proxy '["https://www.googleapis.com/auth/admin.reports.usage.readonly"] Source #

View usage reports for your G Suite domain

adminReportsAuditReadOnlyScope :: Proxy '["https://www.googleapis.com/auth/admin.reports.audit.readonly"] Source #

View audit reports for your G Suite domain

UsageReportParametersItem

data UsageReportParametersItem Source #

Instances
Eq UsageReportParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data UsageReportParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: UsageReportParametersItem -> Constr #

dataTypeOf :: UsageReportParametersItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show UsageReportParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic UsageReportParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep UsageReportParametersItem :: Type -> Type #

ToJSON UsageReportParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON UsageReportParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReportParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReportParametersItem = D1 (MetaData "UsageReportParametersItem" "Network.Google.Reports.Types.Product" "gogol-admin-reports-0.5.0-9bcFr5FmZ1h8uUi7Dnqf7F" False) (C1 (MetaCons "UsageReportParametersItem'" PrefixI True) ((S1 (MetaSel (Just "_urpiDatetimeValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')) :*: (S1 (MetaSel (Just "_urpiBoolValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_urpiIntValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))))) :*: (S1 (MetaSel (Just "_urpiStringValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_urpiName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_urpiMsgValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UsageReportParametersItemMsgValueItem]))))))

usageReportParametersItem :: UsageReportParametersItem Source #

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

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

urpiDatetimeValue :: Lens' UsageReportParametersItem (Maybe UTCTime) Source #

RFC 3339 formatted value of the parameter.

urpiBoolValue :: Lens' UsageReportParametersItem (Maybe Bool) Source #

Boolean value of the parameter.

urpiIntValue :: Lens' UsageReportParametersItem (Maybe Int64) Source #

Integral value of the parameter.

urpiStringValue :: Lens' UsageReportParametersItem (Maybe Text) Source #

String value of the parameter.

urpiName :: Lens' UsageReportParametersItem (Maybe Text) Source #

The name of the parameter.

ActivityId

data ActivityId Source #

Unique identifier for each activity record.

See: activityId smart constructor.

Instances
Eq ActivityId Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data ActivityId Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: ActivityId -> Constr #

dataTypeOf :: ActivityId -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ActivityId Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic ActivityId Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep ActivityId :: Type -> Type #

ToJSON ActivityId Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON ActivityId Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep ActivityId Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep ActivityId = D1 (MetaData "ActivityId" "Network.Google.Reports.Types.Product" "gogol-admin-reports-0.5.0-9bcFr5FmZ1h8uUi7Dnqf7F" False) (C1 (MetaCons "ActivityId'" PrefixI True) ((S1 (MetaSel (Just "_aiTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')) :*: S1 (MetaSel (Just "_aiUniqueQualifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) :*: (S1 (MetaSel (Just "_aiCustomerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_aiApplicationName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

activityId :: ActivityId Source #

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

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

aiTime :: Lens' ActivityId (Maybe UTCTime) Source #

Time of occurrence of the activity.

aiUniqueQualifier :: Lens' ActivityId (Maybe Int64) Source #

Unique qualifier if multiple events have the same time.

aiCustomerId :: Lens' ActivityId (Maybe Text) Source #

Obfuscated customer ID of the source customer.

aiApplicationName :: Lens' ActivityId (Maybe Text) Source #

Application name to which the event belongs.

UsageReports

data UsageReports Source #

JSON template for a collection of usage reports.

See: usageReports smart constructor.

Instances
Eq UsageReports Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data UsageReports Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: UsageReports -> Constr #

dataTypeOf :: UsageReports -> DataType #

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

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

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

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

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

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

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

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

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

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

Show UsageReports Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic UsageReports Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep UsageReports :: Type -> Type #

ToJSON UsageReports Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON UsageReports Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReports Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReports = D1 (MetaData "UsageReports" "Network.Google.Reports.Types.Product" "gogol-admin-reports-0.5.0-9bcFr5FmZ1h8uUi7Dnqf7F" False) (C1 (MetaCons "UsageReports'" PrefixI True) ((S1 (MetaSel (Just "_urEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_urNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_urUsageReports") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UsageReport])) :*: (S1 (MetaSel (Just "_urKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_urWarnings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UsageReportsWarningsItem]))))))

usageReports :: UsageReports Source #

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

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

urEtag :: Lens' UsageReports (Maybe Text) Source #

ETag of the resource.

urNextPageToken :: Lens' UsageReports (Maybe Text) Source #

Token for retrieving the next page

urUsageReports :: Lens' UsageReports [UsageReport] Source #

Various application parameter records.

urKind :: Lens' UsageReports Text Source #

The kind of object.

UsageReportParametersItemMsgValueItem

data UsageReportParametersItemMsgValueItem Source #

Instances
Eq UsageReportParametersItemMsgValueItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data UsageReportParametersItemMsgValueItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: UsageReportParametersItemMsgValueItem -> Constr #

dataTypeOf :: UsageReportParametersItemMsgValueItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show UsageReportParametersItemMsgValueItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic UsageReportParametersItemMsgValueItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

ToJSON UsageReportParametersItemMsgValueItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON UsageReportParametersItemMsgValueItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReportParametersItemMsgValueItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReportParametersItemMsgValueItem = D1 (MetaData "UsageReportParametersItemMsgValueItem" "Network.Google.Reports.Types.Product" "gogol-admin-reports-0.5.0-9bcFr5FmZ1h8uUi7Dnqf7F" True) (C1 (MetaCons "UsageReportParametersItemMsgValueItem'" PrefixI True) (S1 (MetaSel (Just "_urpimviAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

usageReportParametersItemMsgValueItem Source #

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

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

Activities

data Activities Source #

JSON template for a collection of activites.

See: activities smart constructor.

Instances
Eq Activities Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data Activities Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: Activities -> Constr #

dataTypeOf :: Activities -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Activities Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic Activities Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep Activities :: Type -> Type #

ToJSON Activities Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON Activities Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep Activities Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep Activities = D1 (MetaData "Activities" "Network.Google.Reports.Types.Product" "gogol-admin-reports-0.5.0-9bcFr5FmZ1h8uUi7Dnqf7F" False) (C1 (MetaCons "Activities'" PrefixI True) ((S1 (MetaSel (Just "_aEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_aNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_aKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_aItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Activity])))))

activities :: Activities Source #

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

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

aEtag :: Lens' Activities (Maybe Text) Source #

ETag of the resource.

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

Token for retrieving the next page

aKind :: Lens' Activities Text Source #

Kind of list response this is.

aItems :: Lens' Activities [Activity] Source #

Each record in read response.

Channel

data Channel Source #

An notification channel used to watch for resource changes.

See: channel smart constructor.

Instances
Eq Channel Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

Data Channel Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: Channel -> Constr #

dataTypeOf :: Channel -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Channel Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic Channel Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep Channel :: Type -> Type #

Methods

from :: Channel -> Rep Channel x #

to :: Rep Channel x -> Channel #

ToJSON Channel Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON Channel Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep Channel Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

channel :: Channel Source #

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

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

cResourceURI :: Lens' Channel (Maybe Text) Source #

A version-specific identifier for the watched resource.

cResourceId :: Lens' Channel (Maybe Text) Source #

An opaque ID that identifies the resource being watched on this channel. Stable across different API versions.

cKind :: Lens' Channel Text Source #

Identifies this as a notification channel used to watch for changes to a resource. Value: the fixed string "api#channel".

cExpiration :: Lens' Channel (Maybe Int64) Source #

Date and time of notification channel expiration, expressed as a Unix timestamp, in milliseconds. Optional.

cToken :: Lens' Channel (Maybe Text) Source #

An arbitrary string delivered to the target address with each notification delivered over this channel. Optional.

cAddress :: Lens' Channel (Maybe Text) Source #

The address where notifications are delivered for this channel.

cPayload :: Lens' Channel (Maybe Bool) Source #

A Boolean value to indicate whether payload is wanted. Optional.

cParams :: Lens' Channel (Maybe ChannelParams) Source #

Additional parameters controlling delivery channel behavior. Optional.

cId :: Lens' Channel (Maybe Text) Source #

A UUID or similar unique string that identifies this channel.

cType :: Lens' Channel (Maybe Text) Source #

The type of delivery mechanism used for this channel.

UsageReport

data UsageReport Source #

JSON template for a usage report.

See: usageReport smart constructor.

Instances
Eq UsageReport Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data UsageReport Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: UsageReport -> Constr #

dataTypeOf :: UsageReport -> DataType #

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

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

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

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

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

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

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

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

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

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

Show UsageReport Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic UsageReport Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep UsageReport :: Type -> Type #

ToJSON UsageReport Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON UsageReport Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReport Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

usageReport :: UsageReport Source #

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

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

uEtag :: Lens' UsageReport (Maybe Text) Source #

ETag of the resource.

uKind :: Lens' UsageReport Text Source #

The kind of object.

uDate :: Lens' UsageReport (Maybe Text) Source #

The date to which the record belongs.

uParameters :: Lens' UsageReport [UsageReportParametersItem] Source #

Parameter value pairs for various applications.

uEntity :: Lens' UsageReport (Maybe UsageReportEntity) Source #

Information about the type of the item.

UsageReportsWarningsItemDataItem

data UsageReportsWarningsItemDataItem Source #

Instances
Eq UsageReportsWarningsItemDataItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data UsageReportsWarningsItemDataItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: UsageReportsWarningsItemDataItem -> Constr #

dataTypeOf :: UsageReportsWarningsItemDataItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show UsageReportsWarningsItemDataItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic UsageReportsWarningsItemDataItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep UsageReportsWarningsItemDataItem :: Type -> Type #

ToJSON UsageReportsWarningsItemDataItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON UsageReportsWarningsItemDataItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReportsWarningsItemDataItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReportsWarningsItemDataItem = D1 (MetaData "UsageReportsWarningsItemDataItem" "Network.Google.Reports.Types.Product" "gogol-admin-reports-0.5.0-9bcFr5FmZ1h8uUi7Dnqf7F" False) (C1 (MetaCons "UsageReportsWarningsItemDataItem'" PrefixI True) (S1 (MetaSel (Just "_urwidiValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_urwidiKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

usageReportsWarningsItemDataItem :: UsageReportsWarningsItemDataItem Source #

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

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

urwidiValue :: Lens' UsageReportsWarningsItemDataItem (Maybe Text) Source #

Value associated with a key-value pair to give detailed information on the warning.

urwidiKey :: Lens' UsageReportsWarningsItemDataItem (Maybe Text) Source #

Key associated with a key-value pair to give detailed information on the warning.

UsageReportsWarningsItem

data UsageReportsWarningsItem Source #

Instances
Eq UsageReportsWarningsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data UsageReportsWarningsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: UsageReportsWarningsItem -> Constr #

dataTypeOf :: UsageReportsWarningsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show UsageReportsWarningsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic UsageReportsWarningsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep UsageReportsWarningsItem :: Type -> Type #

ToJSON UsageReportsWarningsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON UsageReportsWarningsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReportsWarningsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReportsWarningsItem = D1 (MetaData "UsageReportsWarningsItem" "Network.Google.Reports.Types.Product" "gogol-admin-reports-0.5.0-9bcFr5FmZ1h8uUi7Dnqf7F" False) (C1 (MetaCons "UsageReportsWarningsItem'" PrefixI True) (S1 (MetaSel (Just "_urwiData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UsageReportsWarningsItemDataItem])) :*: (S1 (MetaSel (Just "_urwiCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_urwiMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

usageReportsWarningsItem :: UsageReportsWarningsItem Source #

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

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

urwiData :: Lens' UsageReportsWarningsItem [UsageReportsWarningsItemDataItem] Source #

Key-Value pairs to give detailed information on the warning.

urwiCode :: Lens' UsageReportsWarningsItem (Maybe Text) Source #

Machine readable code / warning type.

urwiMessage :: Lens' UsageReportsWarningsItem (Maybe Text) Source #

Human readable message for the warning.

ActivityEventsItem

data ActivityEventsItem Source #

Instances
Eq ActivityEventsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data ActivityEventsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: ActivityEventsItem -> Constr #

dataTypeOf :: ActivityEventsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ActivityEventsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic ActivityEventsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep ActivityEventsItem :: Type -> Type #

ToJSON ActivityEventsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON ActivityEventsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep ActivityEventsItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep ActivityEventsItem = D1 (MetaData "ActivityEventsItem" "Network.Google.Reports.Types.Product" "gogol-admin-reports-0.5.0-9bcFr5FmZ1h8uUi7Dnqf7F" False) (C1 (MetaCons "ActivityEventsItem'" PrefixI True) (S1 (MetaSel (Just "_aeiName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_aeiParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ActivityEventsItemParametersItem])) :*: S1 (MetaSel (Just "_aeiType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

activityEventsItem :: ActivityEventsItem Source #

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

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

aeiParameters :: Lens' ActivityEventsItem [ActivityEventsItemParametersItem] Source #

Parameter value pairs for various applications.

ChannelParams

data ChannelParams Source #

Additional parameters controlling delivery channel behavior. Optional.

See: channelParams smart constructor.

Instances
Eq ChannelParams Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data ChannelParams Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: ChannelParams -> Constr #

dataTypeOf :: ChannelParams -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ChannelParams Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic ChannelParams Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep ChannelParams :: Type -> Type #

ToJSON ChannelParams Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON ChannelParams Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep ChannelParams Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep ChannelParams = D1 (MetaData "ChannelParams" "Network.Google.Reports.Types.Product" "gogol-admin-reports-0.5.0-9bcFr5FmZ1h8uUi7Dnqf7F" True) (C1 (MetaCons "ChannelParams'" PrefixI True) (S1 (MetaSel (Just "_cpAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text Text))))

channelParams Source #

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

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

cpAddtional :: Lens' ChannelParams (HashMap Text Text) Source #

Declares a new parameter by name.

Activity

data Activity Source #

JSON template for the activity resource.

See: activity smart constructor.

Instances
Eq Activity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data Activity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: Activity -> Constr #

dataTypeOf :: Activity -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Activity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic Activity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep Activity :: Type -> Type #

Methods

from :: Activity -> Rep Activity x #

to :: Rep Activity x -> Activity #

ToJSON Activity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON Activity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep Activity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

activity :: Activity Source #

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

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

actEtag :: Lens' Activity (Maybe Text) Source #

ETag of the entry.

actIPAddress :: Lens' Activity (Maybe Text) Source #

IP Address of the user doing the action.

actKind :: Lens' Activity Text Source #

Kind of resource this is.

actActor :: Lens' Activity (Maybe ActivityActor) Source #

User doing the action.

actOwnerDomain :: Lens' Activity (Maybe Text) Source #

Domain of source customer.

actId :: Lens' Activity (Maybe ActivityId) Source #

Unique identifier for each activity record.

UsageReportEntity

data UsageReportEntity Source #

Information about the type of the item.

See: usageReportEntity smart constructor.

Instances
Eq UsageReportEntity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data UsageReportEntity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: UsageReportEntity -> Constr #

dataTypeOf :: UsageReportEntity -> DataType #

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

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

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

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

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

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

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

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

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

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

Show UsageReportEntity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic UsageReportEntity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep UsageReportEntity :: Type -> Type #

ToJSON UsageReportEntity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON UsageReportEntity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReportEntity Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep UsageReportEntity = D1 (MetaData "UsageReportEntity" "Network.Google.Reports.Types.Product" "gogol-admin-reports-0.5.0-9bcFr5FmZ1h8uUi7Dnqf7F" False) (C1 (MetaCons "UsageReportEntity'" PrefixI True) ((S1 (MetaSel (Just "_ureProFileId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ureCustomerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_ureUserEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_ureType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ureEntityId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

usageReportEntity :: UsageReportEntity Source #

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

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

ureProFileId :: Lens' UsageReportEntity (Maybe Text) Source #

Obfuscated user id for the record.

ureCustomerId :: Lens' UsageReportEntity (Maybe Text) Source #

Obfuscated customer id for the record.

ureUserEmail :: Lens' UsageReportEntity (Maybe Text) Source #

user's email. Only relevant if entity.type = "USER"

ureType :: Lens' UsageReportEntity (Maybe Text) Source #

The type of item, can be customer, user, or entity (aka. object).

ureEntityId :: Lens' UsageReportEntity (Maybe Text) Source #

Object key. Only relevant if entity.type = "OBJECT" Note: external-facing name of report is "Entities" rather than "Objects".

ActivityEventsItemParametersItem

data ActivityEventsItemParametersItem Source #

Instances
Eq ActivityEventsItemParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data ActivityEventsItemParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: ActivityEventsItemParametersItem -> Constr #

dataTypeOf :: ActivityEventsItemParametersItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ActivityEventsItemParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic ActivityEventsItemParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep ActivityEventsItemParametersItem :: Type -> Type #

ToJSON ActivityEventsItemParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON ActivityEventsItemParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep ActivityEventsItemParametersItem Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep ActivityEventsItemParametersItem = D1 (MetaData "ActivityEventsItemParametersItem" "Network.Google.Reports.Types.Product" "gogol-admin-reports-0.5.0-9bcFr5FmZ1h8uUi7Dnqf7F" False) (C1 (MetaCons "ActivityEventsItemParametersItem'" PrefixI True) ((S1 (MetaSel (Just "_aeipiBoolValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 (MetaSel (Just "_aeipiIntValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))) :*: S1 (MetaSel (Just "_aeipiValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_aeipiMultiIntValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Int64])) :*: (S1 (MetaSel (Just "_aeipiName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_aeipiMultiValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))))

activityEventsItemParametersItem :: ActivityEventsItemParametersItem Source #

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

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

aeipiMultiValue :: Lens' ActivityEventsItemParametersItem [Text] Source #

Multi-string value of the parameter.

ActivityActor

data ActivityActor Source #

User doing the action.

See: activityActor smart constructor.

Instances
Eq ActivityActor Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Data ActivityActor Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Methods

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

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

toConstr :: ActivityActor -> Constr #

dataTypeOf :: ActivityActor -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ActivityActor Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Generic ActivityActor Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

Associated Types

type Rep ActivityActor :: Type -> Type #

ToJSON ActivityActor Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

FromJSON ActivityActor Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep ActivityActor Source # 
Instance details

Defined in Network.Google.Reports.Types.Product

type Rep ActivityActor = D1 (MetaData "ActivityActor" "Network.Google.Reports.Types.Product" "gogol-admin-reports-0.5.0-9bcFr5FmZ1h8uUi7Dnqf7F" False) (C1 (MetaCons "ActivityActor'" PrefixI True) ((S1 (MetaSel (Just "_aaEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_aaCallerType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_aaProFileId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_aaKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

activityActor :: ActivityActor Source #

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

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

aaEmail :: Lens' ActivityActor (Maybe Text) Source #

Email address of the user.

aaCallerType :: Lens' ActivityActor (Maybe Text) Source #

User or OAuth 2LO request.

aaProFileId :: Lens' ActivityActor (Maybe Text) Source #

Obfuscated user id of the user.

aaKey :: Lens' ActivityActor (Maybe Text) Source #

For OAuth 2LO API requests, consumer_key of the requestor.