gogol-tracing-0.4.0: Google Tracing 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.Tracing.Types

Contents

Description

 
Synopsis

Service Configuration

tracingService :: ServiceConfig Source #

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

OAuth Scopes

traceAppendScope :: Proxy '["https://www.googleapis.com/auth/trace.append"] Source #

Write Trace data for a project or application

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

Read Trace data for a project or application

cloudPlatformScope :: Proxy '["https://www.googleapis.com/auth/cloud-platform"] Source #

View and manage your data across Google Cloud Platform services

Span

data Span Source #

A span represents a single operation within a trace. Spans can be nested to form a trace tree. Often, a trace contains a root span that describes the end-to-end latency and, optionally, one or more subspans for its sub-operations. (A trace could alternatively contain multiple root spans, or none at all.) Spans do not need to be contiguous. There may be gaps and/or overlaps between spans in a trace.

See: span smart constructor.

Instances
Eq Span Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

Data Span Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: Span -> Constr #

dataTypeOf :: Span -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Span Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

Generic Span Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep Span :: Type -> Type #

Methods

from :: Span -> Rep Span x #

to :: Rep Span x -> Span #

ToJSON Span Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON Span Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Span Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

span :: Span Source #

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

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

sStatus :: Lens' Span (Maybe Status) Source #

An optional final status for this span.

sStartTime :: Lens' Span (Maybe UTCTime) Source #

Start time of the span. On the client side, this is the local machine clock time at which the span execution was started; on the server side, this is the time at which the server application handler started running.

sName :: Lens' Span (Maybe Text) Source #

The resource name of Span in the format `projects/PROJECT_ID/traces/TRACE_ID/spans/SPAN_ID`. `TRACE_ID` is a unique identifier for a trace within a project and is a base16-encoded, case-insensitive string and is required to be 32 char long. `SPAN_ID` is a unique identifier for a span within a trace. It is a base 16-encoded, case-insensitive string of a 8-bytes array and is required to be 16 char long.

sStackTrace :: Lens' Span (Maybe StackTrace) Source #

Stack trace captured at the start of the span.

sAttributes :: Lens' Span (Maybe Attributes) Source #

A set of attributes on the span. A maximum of 32 attributes are allowed per Span.

sEndTime :: Lens' Span (Maybe UTCTime) Source #

End time of the span. On the client side, this is the local machine clock time at which the span execution was ended; on the server side, this is the time at which the server application handler stopped running.

sTimeEvents :: Lens' Span (Maybe TimeEvents) Source #

A maximum of 32 annotations and 128 network events are allowed per Span.

sDisplayName :: Lens' Span (Maybe TruncatableString) Source #

Description of the operation in the span. It is sanitized and displayed in the Stackdriver Trace tool in the {% dynamic print site_values.console_name %}. The display_name may be a method name or some other per-call site name. For the same executable and the same call point, a best practice is to use a consistent operation name, which makes it easier to correlate cross-trace spans. The maximum length for the display_name is 128 bytes.

sParentSpanId :: Lens' Span (Maybe Text) Source #

ID of parent span which is a base 16-encoded, case-insensitive string of a 8-bytes array and is required to be 16 char long. If this is a root span, the value must be empty.

sLinks :: Lens' Span (Maybe Links) Source #

A maximum of 128 links are allowed per Span.

sSpanId :: Lens' Span (Maybe Text) Source #

Unique identifier for a span within a trace. It is a base 16-encoded, case-insensitive string of a 8-bytes array and is required.

TruncatableString

data TruncatableString Source #

Represents a string value that might be truncated.

See: truncatableString smart constructor.

Instances
Eq TruncatableString Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data TruncatableString Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: TruncatableString -> Constr #

dataTypeOf :: TruncatableString -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TruncatableString Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic TruncatableString Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep TruncatableString :: Type -> Type #

ToJSON TruncatableString Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON TruncatableString Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep TruncatableString Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep TruncatableString = D1 (MetaData "TruncatableString" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "TruncatableString'" PrefixI True) (S1 (MetaSel (Just "_tsTruncatedCharacterCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_tsValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

truncatableString :: TruncatableString Source #

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

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

tsTruncatedCharacterCount :: Lens' TruncatableString (Maybe Int32) Source #

The number of characters truncated from the original string value. If 0 it means that the string value was not truncated.

tsValue :: Lens' TruncatableString (Maybe Text) Source #

The truncated string value. E.g. for a string attribute this may have up to 256 bytes.

Status

data Status Source #

The `Status` type defines a logical error model that is suitable for different programming environments, including REST APIs and RPC APIs. It is used by gRPC. The error model is designed to be: - Simple to use and understand for most users - Flexible enough to meet unexpected needs # Overview The `Status` message contains three pieces of data: error code, error message, and error details. The error code should be an enum value of google.rpc.Code, but it may accept additional error codes if needed. The error message should be a developer-facing English message that helps developers *understand* and *resolve* the error. If a localized user-facing error message is needed, put the localized message in the error details or localize it in the client. The optional error details may contain arbitrary information about the error. There is a predefined set of error detail types in the package `google.rpc` that can be used for common error conditions. # Language mapping The `Status` message is the logical representation of the error model, but it is not necessarily the actual wire format. When the `Status` message is exposed in different client libraries and different wire protocols, it can be mapped differently. For example, it will likely be mapped to some exceptions in Java, but more likely mapped to some error codes in C. # Other uses The error model and the `Status` message can be used in a variety of environments, either with or without APIs, to provide a consistent developer experience across different environments. Example uses of this error model include: - Partial errors. If a service needs to return partial errors to the client, it may embed the `Status` in the normal response to indicate the partial errors. - Workflow errors. A typical workflow has multiple steps. Each step may have a `Status` message for error reporting. - Batch operations. If a client uses batch request and batch response, the `Status` message should be used directly inside batch response, one for each error sub-response. - Asynchronous operations. If an API call embeds asynchronous operation results in its response, the status of those operations should be represented directly using the `Status` message. - Logging. If some API errors are stored in logs, the message `Status` could be used directly after any stripping needed for security/privacy reasons.

See: status smart constructor.

Instances
Eq Status Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

Data Status Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: Status -> Constr #

dataTypeOf :: Status -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Status Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic Status Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep Status :: Type -> Type #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

ToJSON Status Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON Status Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Status Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Status = D1 (MetaData "Status" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "Status'" PrefixI True) (S1 (MetaSel (Just "_sDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [StatusDetailsItem])) :*: (S1 (MetaSel (Just "_sCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_sMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

status :: Status Source #

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

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

sDetails :: Lens' Status [StatusDetailsItem] Source #

A list of messages that carry the error details. There will be a common set of message types for APIs to use.

sCode :: Lens' Status (Maybe Int32) Source #

The status code, which should be an enum value of google.rpc.Code.

sMessage :: Lens' Status (Maybe Text) Source #

A developer-facing error message, which should be in English. Any user-facing error message should be localized and sent in the google.rpc.Status.details field, or localized by the client.

AttributesAttributeMap

data AttributesAttributeMap Source #

The maximum key length is 128 bytes (attributes are dropped if the key size is larger than the maximum allowed). The value can be a string (up to 256 bytes), integer, or boolean (true/false). Some common pair examples: "/instance_id": "my-instance" "/zone": "us-central1-a" "/grpc/peer_address": "ip:port" (dns, etc.) "/grpc/deadline": "Duration" "/http/user_agent" "/http/request_bytes": 300 "/http/response_bytes": 1200 "/http/url": google.com/apis "abc.com/myattribute": true

See: attributesAttributeMap smart constructor.

Instances
Eq AttributesAttributeMap Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data AttributesAttributeMap Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: AttributesAttributeMap -> Constr #

dataTypeOf :: AttributesAttributeMap -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AttributesAttributeMap Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic AttributesAttributeMap Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep AttributesAttributeMap :: Type -> Type #

ToJSON AttributesAttributeMap Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON AttributesAttributeMap Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep AttributesAttributeMap Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep AttributesAttributeMap = D1 (MetaData "AttributesAttributeMap" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" True) (C1 (MetaCons "AttributesAttributeMap'" PrefixI True) (S1 (MetaSel (Just "_aamAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text AttributeValue))))

attributesAttributeMap Source #

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

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

Annotation

data Annotation Source #

Text annotation with a set of attributes. A maximum of 32 annotations are allowed per Span.

See: annotation smart constructor.

Instances
Eq Annotation Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data Annotation Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: Annotation -> Constr #

dataTypeOf :: Annotation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Annotation Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic Annotation Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep Annotation :: Type -> Type #

ToJSON Annotation Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON Annotation Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Annotation Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Annotation = D1 (MetaData "Annotation" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "Annotation'" PrefixI True) (S1 (MetaSel (Just "_aAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Attributes)) :*: S1 (MetaSel (Just "_aDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TruncatableString))))

annotation :: Annotation Source #

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

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

aAttributes :: Lens' Annotation (Maybe Attributes) Source #

A set of attributes on the annotation. A maximum of 4 attributes are allowed per Annotation.

aDescription :: Lens' Annotation (Maybe TruncatableString) Source #

A user-supplied message describing the event. The maximum length for the description is 256 bytes.

AttributeValue

data AttributeValue Source #

The allowed types for the value side of an attribute key:value pair.

See: attributeValue smart constructor.

Instances
Eq AttributeValue Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data AttributeValue Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: AttributeValue -> Constr #

dataTypeOf :: AttributeValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AttributeValue Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic AttributeValue Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep AttributeValue :: Type -> Type #

ToJSON AttributeValue Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON AttributeValue Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep AttributeValue Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep AttributeValue = D1 (MetaData "AttributeValue" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "AttributeValue'" PrefixI True) (S1 (MetaSel (Just "_avBoolValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 (MetaSel (Just "_avIntValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))) :*: S1 (MetaSel (Just "_avStringValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TruncatableString)))))

attributeValue :: AttributeValue Source #

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

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

avStringValue :: Lens' AttributeValue (Maybe TruncatableString) Source #

A string value (up to 256 bytes).

NetworkEventType

data NetworkEventType Source #

Type of NetworkEvent. Indicates whether the RPC message was sent or received.

Constructors

TypeUnspecified

TYPE_UNSPECIFIED Unknown event type.

Sent

SENT Indicates a sent RPC message.

Recv

RECV Indicates a received RPC message.

Instances
Enum NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Eq NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Data NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Methods

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

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

toConstr :: NetworkEventType -> Constr #

dataTypeOf :: NetworkEventType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Read NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Show NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Generic NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Associated Types

type Rep NetworkEventType :: Type -> Type #

Hashable NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

ToJSON NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

FromJSON NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

FromHttpApiData NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

ToHttpApiData NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

type Rep NetworkEventType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

type Rep NetworkEventType = D1 (MetaData "NetworkEventType" "Network.Google.Tracing.Types.Sum" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "TypeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Sent" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Recv" PrefixI False) (U1 :: Type -> Type)))

Empty

data Empty Source #

A generic empty message that you can re-use to avoid defining duplicated empty messages in your APIs. A typical example is to use it as the request or the response type of an API method. For instance: service Foo { rpc Bar(google.protobuf.Empty) returns (google.protobuf.Empty); } The JSON representation for `Empty` is empty JSON object `{}`.

See: empty smart constructor.

Instances
Eq Empty Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

Data Empty Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: Empty -> Constr #

dataTypeOf :: Empty -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Empty Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

showsPrec :: Int -> Empty -> ShowS #

show :: Empty -> String #

showList :: [Empty] -> ShowS #

Generic Empty Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep Empty :: Type -> Type #

Methods

from :: Empty -> Rep Empty x #

to :: Rep Empty x -> Empty #

ToJSON Empty Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON Empty Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Empty Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Empty = D1 (MetaData "Empty" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "Empty'" PrefixI False) (U1 :: Type -> Type))

empty :: Empty Source #

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

Link

data Link Source #

A pointer from this span to another span in a different `Trace` within the same service project or within a different service project. Used (for example) in batching operations, where a single batch handler processes multiple requests from different traces or when receives a request from a different service project.

See: link smart constructor.

link :: Link Source #

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

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

lTraceId :: Lens' Link (Maybe Text) Source #

`TRACE_ID` is a unique identifier for a trace within a project. It is a base16-encoded, case-insensitive string of a 16-bytes array and is required to be 32 char long.

lType :: Lens' Link (Maybe LinkType) Source #

The relationship of the current span relative to the linked span.

lSpanId :: Lens' Link (Maybe Text) Source #

`SPAN_ID` is a unique identifier for a span within a trace. It is a base16-encoded, case-insensitive string of a 8-bytes array and is required to be 16 char long.

StatusDetailsItem

data StatusDetailsItem Source #

Instances
Eq StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: StatusDetailsItem -> Constr #

dataTypeOf :: StatusDetailsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep StatusDetailsItem :: Type -> Type #

ToJSON StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep StatusDetailsItem Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep StatusDetailsItem = D1 (MetaData "StatusDetailsItem" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" True) (C1 (MetaCons "StatusDetailsItem'" PrefixI True) (S1 (MetaSel (Just "_sdiAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

statusDetailsItem Source #

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

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

sdiAddtional :: Lens' StatusDetailsItem (HashMap Text JSONValue) Source #

Properties of the object. Contains field 'type with type URL.

ListSpansResponse

data ListSpansResponse Source #

The response message for the `ListSpans` method.

See: listSpansResponse smart constructor.

Instances
Eq ListSpansResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data ListSpansResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: ListSpansResponse -> Constr #

dataTypeOf :: ListSpansResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ListSpansResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic ListSpansResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep ListSpansResponse :: Type -> Type #

ToJSON ListSpansResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON ListSpansResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep ListSpansResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep ListSpansResponse = D1 (MetaData "ListSpansResponse" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "ListSpansResponse'" PrefixI True) (S1 (MetaSel (Just "_lsrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lsrSpans") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Span]))))

listSpansResponse :: ListSpansResponse Source #

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

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

lsrNextPageToken :: Lens' ListSpansResponse (Maybe Text) Source #

If defined, indicates that there are more spans that match the request. Pass this as the value of `pageToken` in a subsequent request to retrieve additional spans.

lsrSpans :: Lens' ListSpansResponse [Span] Source #

The requested spans if there are any in the specified trace.

StackTrace

data StackTrace Source #

StackTrace collected in a trace.

See: stackTrace smart constructor.

Instances
Eq StackTrace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data StackTrace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: StackTrace -> Constr #

dataTypeOf :: StackTrace -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StackTrace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic StackTrace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep StackTrace :: Type -> Type #

ToJSON StackTrace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON StackTrace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep StackTrace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep StackTrace = D1 (MetaData "StackTrace" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "StackTrace'" PrefixI True) (S1 (MetaSel (Just "_stStackTraceHashId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Word64))) :*: S1 (MetaSel (Just "_stStackFrames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe StackFrames))))

stackTrace :: StackTrace Source #

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

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

stStackTraceHashId :: Lens' StackTrace (Maybe Word64) Source #

The hash ID is used to conserve network bandwidth for duplicate stack traces within a single trace. Often multiple spans will have identical stack traces. The first occurrence of a stack trace should contain both the `stackFrame` content and a value in `stackTraceHashId`. Subsequent spans within the same request can refer to that stack trace by only setting `stackTraceHashId`.

stStackFrames :: Lens' StackTrace (Maybe StackFrames) Source #

Stack frames in this stack trace. A maximum of 128 frames are allowed.

BatchWriteSpansRequest

data BatchWriteSpansRequest Source #

The request message for the `BatchWriteSpans` method.

See: batchWriteSpansRequest smart constructor.

Instances
Eq BatchWriteSpansRequest Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data BatchWriteSpansRequest Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: BatchWriteSpansRequest -> Constr #

dataTypeOf :: BatchWriteSpansRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BatchWriteSpansRequest Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic BatchWriteSpansRequest Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep BatchWriteSpansRequest :: Type -> Type #

ToJSON BatchWriteSpansRequest Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON BatchWriteSpansRequest Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep BatchWriteSpansRequest Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep BatchWriteSpansRequest = D1 (MetaData "BatchWriteSpansRequest" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" True) (C1 (MetaCons "BatchWriteSpansRequest'" PrefixI True) (S1 (MetaSel (Just "_bwsrSpans") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Span]))))

batchWriteSpansRequest :: BatchWriteSpansRequest Source #

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

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

bwsrSpans :: Lens' BatchWriteSpansRequest [Span] Source #

A collection of spans.

Attributes

data Attributes Source #

Attributes of a span with a key:value format.

See: attributes smart constructor.

Instances
Eq Attributes Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data Attributes Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: Attributes -> Constr #

dataTypeOf :: Attributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Attributes Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic Attributes Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep Attributes :: Type -> Type #

ToJSON Attributes Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON Attributes Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Attributes Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Attributes = D1 (MetaData "Attributes" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "Attributes'" PrefixI True) (S1 (MetaSel (Just "_aDroppedAttributesCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_aAttributeMap") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AttributesAttributeMap))))

attributes :: Attributes Source #

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

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

aDroppedAttributesCount :: Lens' Attributes (Maybe Int32) Source #

The number of dropped attributes after the maximum size was enforced. If 0 then no attributes were dropped.

aAttributeMap :: Lens' Attributes (Maybe AttributesAttributeMap) Source #

The maximum key length is 128 bytes (attributes are dropped if the key size is larger than the maximum allowed). The value can be a string (up to 256 bytes), integer, or boolean (true/false). Some common pair examples: "/instance_id": "my-instance" "/zone": "us-central1-a" "/grpc/peer_address": "ip:port" (dns, etc.) "/grpc/deadline": "Duration" "/http/user_agent" "/http/request_bytes": 300 "/http/response_bytes": 1200 "/http/url": google.com/apis "abc.com/myattribute": true

NetworkEvent

data NetworkEvent Source #

An event describing an RPC message sent/received on the network. A maximum of 128 network events are allowed per Span.

See: networkEvent smart constructor.

Instances
Eq NetworkEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data NetworkEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: NetworkEvent -> Constr #

dataTypeOf :: NetworkEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show NetworkEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic NetworkEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep NetworkEvent :: Type -> Type #

ToJSON NetworkEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON NetworkEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep NetworkEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep NetworkEvent = D1 (MetaData "NetworkEvent" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "NetworkEvent'" PrefixI True) ((S1 (MetaSel (Just "_neTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')) :*: S1 (MetaSel (Just "_neMessageSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Word64)))) :*: (S1 (MetaSel (Just "_neType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NetworkEventType)) :*: S1 (MetaSel (Just "_neMessageId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Word64))))))

networkEvent :: NetworkEvent Source #

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

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

neTime :: Lens' NetworkEvent (Maybe UTCTime) Source #

If available, this is the kernel time: * For sent messages, this is the time at which the first bit was sent. * For received messages, this is the time at which the last bit was received.

neMessageSize :: Lens' NetworkEvent (Maybe Word64) Source #

The number of bytes sent or received.

neType :: Lens' NetworkEvent (Maybe NetworkEventType) Source #

Type of NetworkEvent. Indicates whether the RPC message was sent or received.

neMessageId :: Lens' NetworkEvent (Maybe Word64) Source #

An identifier for the message, which must be unique in this span.

Module

data Module Source #

Binary module.

See: module' smart constructor.

Instances
Eq Module Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

Data Module Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: Module -> Constr #

dataTypeOf :: Module -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Module Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic Module Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep Module :: Type -> Type #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

ToJSON Module Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON Module Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Module Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Module = D1 (MetaData "Module" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "Module'" PrefixI True) (S1 (MetaSel (Just "_mBuildId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TruncatableString)) :*: S1 (MetaSel (Just "_mModule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TruncatableString))))

module' :: Module Source #

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

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

mBuildId :: Lens' Module (Maybe TruncatableString) Source #

Build_id is a unique identifier for the module, usually a hash of its contents (up to 128 characters).

mModule :: Lens' Module (Maybe TruncatableString) Source #

E.g. main binary, kernel modules, and dynamic libraries such as libc.so, sharedlib.so (up to 256 characters).

TimeEvents

data TimeEvents Source #

A collection of `TimeEvent`s. A `TimeEvent` is a time-stamped annotation on the span, consisting of either user-supplied key:value pairs, or details of an RPC message sent/received on the network.

See: timeEvents smart constructor.

Instances
Eq TimeEvents Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data TimeEvents Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: TimeEvents -> Constr #

dataTypeOf :: TimeEvents -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TimeEvents Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic TimeEvents Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep TimeEvents :: Type -> Type #

ToJSON TimeEvents Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON TimeEvents Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep TimeEvents Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep TimeEvents = D1 (MetaData "TimeEvents" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "TimeEvents'" PrefixI True) (S1 (MetaSel (Just "_teDroppedAnnotationsCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: (S1 (MetaSel (Just "_teDroppedNetworkEventsCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_teTimeEvent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [TimeEvent])))))

timeEvents :: TimeEvents Source #

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

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

teDroppedAnnotationsCount :: Lens' TimeEvents (Maybe Int32) Source #

The number of dropped annotations after the maximum size was enforced. If 0 then no annotations were dropped.

teDroppedNetworkEventsCount :: Lens' TimeEvents (Maybe Int32) Source #

The number of dropped network events after the maximum size was enforced. If 0 then no annotations were dropped.

teTimeEvent :: Lens' TimeEvents [TimeEvent] Source #

A collection of `TimeEvent`s.

Xgafv

data Xgafv Source #

V1 error format.

Constructors

X1

1 v1 error format

X2

2 v2 error format

Instances
Enum Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Eq Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Methods

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

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

Data Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Methods

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

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

toConstr :: Xgafv -> Constr #

dataTypeOf :: Xgafv -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Methods

compare :: Xgafv -> Xgafv -> Ordering #

(<) :: Xgafv -> Xgafv -> Bool #

(<=) :: Xgafv -> Xgafv -> Bool #

(>) :: Xgafv -> Xgafv -> Bool #

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

max :: Xgafv -> Xgafv -> Xgafv #

min :: Xgafv -> Xgafv -> Xgafv #

Read Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Show Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Methods

showsPrec :: Int -> Xgafv -> ShowS #

show :: Xgafv -> String #

showList :: [Xgafv] -> ShowS #

Generic Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Associated Types

type Rep Xgafv :: Type -> Type #

Methods

from :: Xgafv -> Rep Xgafv x #

to :: Rep Xgafv x -> Xgafv #

Hashable Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Methods

hashWithSalt :: Int -> Xgafv -> Int #

hash :: Xgafv -> Int #

ToJSON Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

FromJSON Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

FromHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

ToHttpApiData Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

type Rep Xgafv Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

type Rep Xgafv = D1 (MetaData "Xgafv" "Network.Google.Tracing.Types.Sum" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "X1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "X2" PrefixI False) (U1 :: Type -> Type))

StackFrames

data StackFrames Source #

Represents collection of StackFrames that can be truncated.

See: stackFrames smart constructor.

Instances
Eq StackFrames Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data StackFrames Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: StackFrames -> Constr #

dataTypeOf :: StackFrames -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StackFrames Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic StackFrames Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep StackFrames :: Type -> Type #

ToJSON StackFrames Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON StackFrames Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep StackFrames Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep StackFrames = D1 (MetaData "StackFrames" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "StackFrames'" PrefixI True) (S1 (MetaSel (Just "_sfDroppedFramesCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_sfFrame") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [StackFrame]))))

stackFrames :: StackFrames Source #

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

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

sfDroppedFramesCount :: Lens' StackFrames (Maybe Int32) Source #

The number of dropped stack frames after the maximum size was enforced. If 0 then no frames were dropped.

sfFrame :: Lens' StackFrames [StackFrame] Source #

Stack frames in this stack trace.

LinkType

data LinkType Source #

The relationship of the current span relative to the linked span.

Constructors

LTTypeUnspecified

TYPE_UNSPECIFIED The relationship of the two spans is unknown.

LTChild

CHILD The current span is a child of the linked span.

LTParent

PARENT The current span is the parent of the linked span.

Instances
Enum LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Eq LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Data LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Methods

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

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

toConstr :: LinkType -> Constr #

dataTypeOf :: LinkType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Read LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Show LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Generic LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Associated Types

type Rep LinkType :: Type -> Type #

Methods

from :: LinkType -> Rep LinkType x #

to :: Rep LinkType x -> LinkType #

Hashable LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

Methods

hashWithSalt :: Int -> LinkType -> Int #

hash :: LinkType -> Int #

ToJSON LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

FromJSON LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

FromHttpApiData LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

ToHttpApiData LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

type Rep LinkType Source # 
Instance details

Defined in Network.Google.Tracing.Types.Sum

type Rep LinkType = D1 (MetaData "LinkType" "Network.Google.Tracing.Types.Sum" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "LTTypeUnspecified" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "LTChild" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LTParent" PrefixI False) (U1 :: Type -> Type)))

StackFrame

data StackFrame Source #

Represents a single stack frame in a stack trace.

See: stackFrame smart constructor.

Instances
Eq StackFrame Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data StackFrame Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: StackFrame -> Constr #

dataTypeOf :: StackFrame -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StackFrame Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic StackFrame Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep StackFrame :: Type -> Type #

ToJSON StackFrame Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON StackFrame Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep StackFrame Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

stackFrame :: StackFrame Source #

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

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

sfLoadModule :: Lens' StackFrame (Maybe Module) Source #

Binary module the code is loaded from.

sfOriginalFunctionName :: Lens' StackFrame (Maybe TruncatableString) Source #

Used when the function name is mangled. May be fully-qualified (up to 1024 characters).

sfLineNumber :: Lens' StackFrame (Maybe Int64) Source #

Line number of the frame.

sfSourceVersion :: Lens' StackFrame (Maybe TruncatableString) Source #

The version of the deployed source code (up to 128 characters).

sfFunctionName :: Lens' StackFrame (Maybe TruncatableString) Source #

The fully-qualified name that uniquely identifies this function or method (up to 1024 characters).

sfColumnNumber :: Lens' StackFrame (Maybe Int64) Source #

Column number is important in JavaScript (anonymous functions). May not be available in some languages.

sfFileName :: Lens' StackFrame (Maybe TruncatableString) Source #

The filename of the file containing this frame (up to 256 characters).

Links

data Links Source #

A collection of links, which are references from this span to a span in the same or different trace.

See: links smart constructor.

links :: Links Source #

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

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

lDroppedLinksCount :: Lens' Links (Maybe Int32) Source #

The number of dropped links after the maximum size was enforced. If 0 then no links were dropped.

lLink :: Lens' Links [Link] Source #

A collection of links.

ListTracesResponse

data ListTracesResponse Source #

The response message for the `ListTraces` method.

See: listTracesResponse smart constructor.

Instances
Eq ListTracesResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data ListTracesResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: ListTracesResponse -> Constr #

dataTypeOf :: ListTracesResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ListTracesResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic ListTracesResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep ListTracesResponse :: Type -> Type #

ToJSON ListTracesResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON ListTracesResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep ListTracesResponse Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep ListTracesResponse = D1 (MetaData "ListTracesResponse" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "ListTracesResponse'" PrefixI True) (S1 (MetaSel (Just "_ltrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ltrTraces") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Trace]))))

listTracesResponse :: ListTracesResponse Source #

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

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

ltrNextPageToken :: Lens' ListTracesResponse (Maybe Text) Source #

If defined, indicates that there are more traces that match the request and that this value should be passed to the next request to continue retrieving additional traces.

ltrTraces :: Lens' ListTracesResponse [Trace] Source #

List of trace records returned.

TimeEvent

data TimeEvent Source #

A time-stamped annotation in the Span.

See: timeEvent smart constructor.

Instances
Eq TimeEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Data TimeEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: TimeEvent -> Constr #

dataTypeOf :: TimeEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TimeEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Generic TimeEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep TimeEvent :: Type -> Type #

ToJSON TimeEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON TimeEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep TimeEvent Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep TimeEvent = D1 (MetaData "TimeEvent" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" False) (C1 (MetaCons "TimeEvent'" PrefixI True) (S1 (MetaSel (Just "_teAnnotation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Annotation)) :*: (S1 (MetaSel (Just "_teTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')) :*: S1 (MetaSel (Just "_teNetworkEvent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NetworkEvent)))))

timeEvent :: TimeEvent Source #

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

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

teAnnotation :: Lens' TimeEvent (Maybe Annotation) Source #

One or more key:value pairs.

teTime :: Lens' TimeEvent (Maybe UTCTime) Source #

The timestamp indicating the time the event occurred.

teNetworkEvent :: Lens' TimeEvent (Maybe NetworkEvent) Source #

An event describing an RPC message sent/received on the network.

Trace

data Trace Source #

A trace describes how long it takes for an application to perform some operations. It consists of a set of spans, each representing an operation and including time information and operation details.

See: trace smart constructor.

Instances
Eq Trace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

Data Trace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

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

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

toConstr :: Trace -> Constr #

dataTypeOf :: Trace -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Trace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Methods

showsPrec :: Int -> Trace -> ShowS #

show :: Trace -> String #

showList :: [Trace] -> ShowS #

Generic Trace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

Associated Types

type Rep Trace :: Type -> Type #

Methods

from :: Trace -> Rep Trace x #

to :: Rep Trace x -> Trace #

ToJSON Trace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

FromJSON Trace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Trace Source # 
Instance details

Defined in Network.Google.Tracing.Types.Product

type Rep Trace = D1 (MetaData "Trace" "Network.Google.Tracing.Types.Product" "gogol-tracing-0.4.0-IYfv4sD5poO9PMAsL7PvYd" True) (C1 (MetaCons "Trace'" PrefixI True) (S1 (MetaSel (Just "_tName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

trace :: Trace Source #

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

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

tName :: Lens' Trace (Maybe Text) Source #

The resource name of Trace in the format `projects/PROJECT_ID/traces/TRACE_ID`. `TRACE_ID` is a unique identifier for a trace within a project and is a base16-encoded, case-insensitive string and is required to be 32 char long.