gogol-latencytest-0.3.0: Google Cloud Network Performance Monitoring 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.LatencyTest

Contents

Description

Synopsis

Service Configuration

latencyTestService :: ServiceConfig Source #

Default request referring to version v2 of the Google Cloud Network Performance Monitoring API. This contains the host and root path used as a starting point for constructing service requests.

OAuth Scopes

monitoringReadOnlyScope :: Proxy '["https://www.googleapis.com/auth/monitoring.readonly"] Source #

View monitoring data for all of your Google Cloud and API projects

API Declaration

type LatencyTestAPI = StatscollectionUpdatestatsResource :<|> StatscollectionUpdateaggregatedstatsResource Source #

Represents the entirety of the methods and resources available for the Google Cloud Network Performance Monitoring API service.

Resources

cloudlatencytest.statscollection.updateaggregatedstats

cloudlatencytest.statscollection.updatestats

Types

IntValue

data IntValue Source #

Instances

Eq IntValue Source # 
Data IntValue Source # 

Methods

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

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

toConstr :: IntValue -> Constr #

dataTypeOf :: IntValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Show IntValue Source # 
Generic IntValue Source # 

Associated Types

type Rep IntValue :: * -> * #

Methods

from :: IntValue -> Rep IntValue x #

to :: Rep IntValue x -> IntValue #

ToJSON IntValue Source # 
FromJSON IntValue Source # 
type Rep IntValue Source # 
type Rep IntValue = D1 (MetaData "IntValue" "Network.Google.LatencyTest.Types.Product" "gogol-latencytest-0.3.0-I1CDDjDz7gUEPJ4JAvfTJ" False) (C1 (MetaCons "IntValue'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ivValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_ivLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

intValue :: IntValue Source #

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

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

DoubleValue

data DoubleValue Source #

Instances

Eq DoubleValue Source # 
Data DoubleValue Source # 

Methods

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

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

toConstr :: DoubleValue -> Constr #

dataTypeOf :: DoubleValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DoubleValue Source # 
Generic DoubleValue Source # 

Associated Types

type Rep DoubleValue :: * -> * #

ToJSON DoubleValue Source # 
FromJSON DoubleValue Source # 
type Rep DoubleValue Source # 
type Rep DoubleValue = D1 (MetaData "DoubleValue" "Network.Google.LatencyTest.Types.Product" "gogol-latencytest-0.3.0-I1CDDjDz7gUEPJ4JAvfTJ" False) (C1 (MetaCons "DoubleValue'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dvValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_dvLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

doubleValue :: DoubleValue Source #

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

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

StringValue

data StringValue Source #

Instances

Eq StringValue Source # 
Data StringValue Source # 

Methods

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

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

toConstr :: StringValue -> Constr #

dataTypeOf :: StringValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StringValue Source # 
Generic StringValue Source # 

Associated Types

type Rep StringValue :: * -> * #

ToJSON StringValue Source # 
FromJSON StringValue Source # 
type Rep StringValue Source # 
type Rep StringValue = D1 (MetaData "StringValue" "Network.Google.LatencyTest.Types.Product" "gogol-latencytest-0.3.0-I1CDDjDz7gUEPJ4JAvfTJ" False) (C1 (MetaCons "StringValue'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_svValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_svLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

stringValue :: StringValue Source #

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

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

AggregatedStatsReply

data AggregatedStatsReply Source #

Instances

Eq AggregatedStatsReply Source # 
Data AggregatedStatsReply Source # 

Methods

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

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

toConstr :: AggregatedStatsReply -> Constr #

dataTypeOf :: AggregatedStatsReply -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AggregatedStatsReply Source # 
Generic AggregatedStatsReply Source # 
ToJSON AggregatedStatsReply Source # 
FromJSON AggregatedStatsReply Source # 
type Rep AggregatedStatsReply Source # 
type Rep AggregatedStatsReply = D1 (MetaData "AggregatedStatsReply" "Network.Google.LatencyTest.Types.Product" "gogol-latencytest-0.3.0-I1CDDjDz7gUEPJ4JAvfTJ" True) (C1 (MetaCons "AggregatedStatsReply'" PrefixI True) (S1 (MetaSel (Just Symbol "_asrTestValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

aggregatedStatsReply :: AggregatedStatsReply Source #

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

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

Stats

data Stats Source #

Instances

Eq Stats Source # 

Methods

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

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

Data Stats Source # 

Methods

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

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

toConstr :: Stats -> Constr #

dataTypeOf :: Stats -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Stats Source # 

Methods

showsPrec :: Int -> Stats -> ShowS #

show :: Stats -> String #

showList :: [Stats] -> ShowS #

Generic Stats Source # 

Associated Types

type Rep Stats :: * -> * #

Methods

from :: Stats -> Rep Stats x #

to :: Rep Stats x -> Stats #

ToJSON Stats Source # 
FromJSON Stats Source # 
type Rep Stats Source # 
type Rep Stats = D1 (MetaData "Stats" "Network.Google.LatencyTest.Types.Product" "gogol-latencytest-0.3.0-I1CDDjDz7gUEPJ4JAvfTJ" False) (C1 (MetaCons "Stats'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_sDoubleValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DoubleValue])))) ((:*:) (S1 (MetaSel (Just Symbol "_sStringValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [StringValue]))) (S1 (MetaSel (Just Symbol "_sIntValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [IntValue]))))))

stats :: Stats Source #

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

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

AggregatedStats

data AggregatedStats Source #

Instances

Eq AggregatedStats Source # 
Data AggregatedStats Source # 

Methods

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

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

toConstr :: AggregatedStats -> Constr #

dataTypeOf :: AggregatedStats -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AggregatedStats Source # 
Generic AggregatedStats Source # 
ToJSON AggregatedStats Source # 
FromJSON AggregatedStats Source # 
type Rep AggregatedStats Source # 
type Rep AggregatedStats = D1 (MetaData "AggregatedStats" "Network.Google.LatencyTest.Types.Product" "gogol-latencytest-0.3.0-I1CDDjDz7gUEPJ4JAvfTJ" True) (C1 (MetaCons "AggregatedStats'" PrefixI True) (S1 (MetaSel (Just Symbol "_asStats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Stats]))))

aggregatedStats :: AggregatedStats Source #

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

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

StatsReply

data StatsReply Source #

Instances

Eq StatsReply Source # 
Data StatsReply Source # 

Methods

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

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

toConstr :: StatsReply -> Constr #

dataTypeOf :: StatsReply -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StatsReply Source # 
Generic StatsReply Source # 

Associated Types

type Rep StatsReply :: * -> * #

ToJSON StatsReply Source # 
FromJSON StatsReply Source # 
type Rep StatsReply Source # 
type Rep StatsReply = D1 (MetaData "StatsReply" "Network.Google.LatencyTest.Types.Product" "gogol-latencytest-0.3.0-I1CDDjDz7gUEPJ4JAvfTJ" True) (C1 (MetaCons "StatsReply'" PrefixI True) (S1 (MetaSel (Just Symbol "_srTestValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

statsReply :: StatsReply Source #

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

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