amazonka-xray-1.6.1: Amazon X-Ray SDK.

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

Network.AWS.XRay

Contents

Description

AWS X-Ray provides APIs for managing debug traces and retrieving service maps and other data created by processing those traces.

Synopsis

Service Configuration

xRay :: Service Source #

API version 2016-04-12 of the Amazon X-Ray SDK configuration.

Errors

Error matchers are designed for use with the functions provided by Control.Exception.Lens. This allows catching (and rethrowing) service specific errors returned by XRay.

InvalidRequestException

_InvalidRequestException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The request is missing required parameters or has invalid parameters.

ThrottledException

_ThrottledException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The request exceeds the maximum number of requests per second.

Waiters

Waiters poll by repeatedly sending a request until some remote success condition configured by the Wait specification is fulfilled. The Wait specification determines how many attempts should be made, in addition to delay and retry strategies.

Operations

Some AWS operations return results that are incomplete and require subsequent requests in order to obtain the entire result set. The process of sending subsequent requests to continue where a previous request left off is called pagination. For example, the ListObjects operation of Amazon S3 returns up to 1000 objects at a time, and you must send subsequent requests with the appropriate Marker in order to retrieve the next page of results.

Operations that have an AWSPager instance can transparently perform subsequent requests, correctly setting Markers and other request facets to iterate through the entire result set of a truncated API operation. Operations which support this have an additional note in the documentation.

Many operations have the ability to filter results on the server side. See the individual operation parameters for details.

PutEncryptionConfig

GetServiceGraph (Paginated)

GetTraceSummaries (Paginated)

PutTraceSegments

BatchGetTraces (Paginated)

GetEncryptionConfig

PutTelemetryRecords

GetTraceGraph (Paginated)

Types

EncryptionStatus

data EncryptionStatus Source #

Constructors

Active 
Updating 
Instances
Bounded EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Enum EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Eq EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Data EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Methods

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

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

toConstr :: EncryptionStatus -> Constr #

dataTypeOf :: EncryptionStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Read EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Show EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Generic EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Associated Types

type Rep EncryptionStatus :: Type -> Type #

Hashable EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

FromJSON EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

ToHeader EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

ToQuery EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

ToByteString EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

FromText EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

ToText EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

NFData EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Methods

rnf :: EncryptionStatus -> () #

type Rep EncryptionStatus Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

type Rep EncryptionStatus = D1 (MetaData "EncryptionStatus" "Network.AWS.XRay.Types.Sum" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "Active" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Updating" PrefixI False) (U1 :: Type -> Type))

EncryptionType

data EncryptionType Source #

Constructors

KMS 
None 
Instances
Bounded EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Enum EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Eq EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Data EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Methods

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

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

toConstr :: EncryptionType -> Constr #

dataTypeOf :: EncryptionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Read EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Show EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Generic EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Associated Types

type Rep EncryptionType :: Type -> Type #

Hashable EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

ToJSON EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

FromJSON EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

ToHeader EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

ToQuery EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

ToByteString EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

FromText EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

ToText EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

NFData EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

Methods

rnf :: EncryptionType -> () #

type Rep EncryptionType Source # 
Instance details

Defined in Network.AWS.XRay.Types.Sum

type Rep EncryptionType = D1 (MetaData "EncryptionType" "Network.AWS.XRay.Types.Sum" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "KMS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "None" PrefixI False) (U1 :: Type -> Type))

Alias

data Alias Source #

An alias for an edge.

See: alias smart constructor.

Instances
Eq Alias Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

Data Alias Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: Alias -> Constr #

dataTypeOf :: Alias -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Alias Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show Alias Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

showsPrec :: Int -> Alias -> ShowS #

show :: Alias -> String #

showList :: [Alias] -> ShowS #

Generic Alias Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep Alias :: Type -> Type #

Methods

from :: Alias -> Rep Alias x #

to :: Rep Alias x -> Alias #

Hashable Alias Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

hashWithSalt :: Int -> Alias -> Int #

hash :: Alias -> Int #

FromJSON Alias Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData Alias Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: Alias -> () #

type Rep Alias Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep Alias = D1 (MetaData "Alias" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "Alias'" PrefixI True) (S1 (MetaSel (Just "_aNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: (S1 (MetaSel (Just "_aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_aType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

alias :: Alias Source #

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

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

  • aNames - A list of names for the alias, including the canonical name.
  • aName - The canonical name of the alias.
  • aType - The type of the alias.

aNames :: Lens' Alias [Text] Source #

A list of names for the alias, including the canonical name.

aName :: Lens' Alias (Maybe Text) Source #

The canonical name of the alias.

aType :: Lens' Alias (Maybe Text) Source #

The type of the alias.

AnnotationValue

data AnnotationValue Source #

Value of a segment annotation. Has one of three value types: Number, Boolean or String.

See: annotationValue smart constructor.

Instances
Eq AnnotationValue Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data AnnotationValue Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: AnnotationValue -> Constr #

dataTypeOf :: AnnotationValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AnnotationValue Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show AnnotationValue Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic AnnotationValue Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep AnnotationValue :: Type -> Type #

Hashable AnnotationValue Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON AnnotationValue Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData AnnotationValue Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: AnnotationValue -> () #

type Rep AnnotationValue Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep AnnotationValue = D1 (MetaData "AnnotationValue" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "AnnotationValue'" PrefixI True) (S1 (MetaSel (Just "_avNumberValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double)) :*: (S1 (MetaSel (Just "_avStringValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_avBooleanValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))

annotationValue :: AnnotationValue Source #

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

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

avNumberValue :: Lens' AnnotationValue (Maybe Double) Source #

Value for a Number annotation.

avStringValue :: Lens' AnnotationValue (Maybe Text) Source #

Value for a String annotation.

avBooleanValue :: Lens' AnnotationValue (Maybe Bool) Source #

Value for a Boolean annotation.

BackendConnectionErrors

data BackendConnectionErrors Source #

See: backendConnectionErrors smart constructor.

Instances
Eq BackendConnectionErrors Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data BackendConnectionErrors Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: BackendConnectionErrors -> Constr #

dataTypeOf :: BackendConnectionErrors -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BackendConnectionErrors Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show BackendConnectionErrors Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic BackendConnectionErrors Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep BackendConnectionErrors :: Type -> Type #

Hashable BackendConnectionErrors Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

ToJSON BackendConnectionErrors Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData BackendConnectionErrors Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: BackendConnectionErrors -> () #

type Rep BackendConnectionErrors Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep BackendConnectionErrors = D1 (MetaData "BackendConnectionErrors" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "BackendConnectionErrors'" PrefixI True) ((S1 (MetaSel (Just "_bceOtherCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 (MetaSel (Just "_bceTimeoutCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_bceHTTPCode5XXCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))) :*: (S1 (MetaSel (Just "_bceConnectionRefusedCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 (MetaSel (Just "_bceHTTPCode4XXCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_bceUnknownHostCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))))

backendConnectionErrors :: BackendConnectionErrors Source #

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

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

Edge

data Edge Source #

Information about a connection between two services.

See: edge smart constructor.

Instances
Eq Edge Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

Data Edge Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: Edge -> Constr #

dataTypeOf :: Edge -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Edge Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show Edge Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

showsPrec :: Int -> Edge -> ShowS #

show :: Edge -> String #

showList :: [Edge] -> ShowS #

Generic Edge Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep Edge :: Type -> Type #

Methods

from :: Edge -> Rep Edge x #

to :: Rep Edge x -> Edge #

Hashable Edge Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

hashWithSalt :: Int -> Edge -> Int #

hash :: Edge -> Int #

FromJSON Edge Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData Edge Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: Edge -> () #

type Rep Edge Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

edge :: Edge Source #

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

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

eStartTime :: Lens' Edge (Maybe UTCTime) Source #

The start time of the first segment on the edge.

eAliases :: Lens' Edge [Alias] Source #

Aliases for the edge.

eResponseTimeHistogram :: Lens' Edge [HistogramEntry] Source #

A histogram that maps the spread of client response times on an edge.

eReferenceId :: Lens' Edge (Maybe Int) Source #

Identifier of the edge. Unique within a service map.

eEndTime :: Lens' Edge (Maybe UTCTime) Source #

The end time of the last segment on the edge.

eSummaryStatistics :: Lens' Edge (Maybe EdgeStatistics) Source #

Response statistics for segments on the edge.

EdgeStatistics

data EdgeStatistics Source #

Response statistics for an edge.

See: edgeStatistics smart constructor.

Instances
Eq EdgeStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data EdgeStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: EdgeStatistics -> Constr #

dataTypeOf :: EdgeStatistics -> DataType #

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

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

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

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

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

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

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

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

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

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

Read EdgeStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show EdgeStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic EdgeStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep EdgeStatistics :: Type -> Type #

Hashable EdgeStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON EdgeStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData EdgeStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: EdgeStatistics -> () #

type Rep EdgeStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep EdgeStatistics = D1 (MetaData "EdgeStatistics" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "EdgeStatistics'" PrefixI True) ((S1 (MetaSel (Just "_esFaultStatistics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FaultStatistics)) :*: S1 (MetaSel (Just "_esOKCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))) :*: (S1 (MetaSel (Just "_esTotalResponseTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double)) :*: (S1 (MetaSel (Just "_esErrorStatistics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ErrorStatistics)) :*: S1 (MetaSel (Just "_esTotalCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))))))

edgeStatistics :: EdgeStatistics Source #

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

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

  • esFaultStatistics - Information about requests that failed with a 5xx Server Error status code.
  • esOKCount - The number of requests that completed with a 2xx Success status code.
  • esTotalResponseTime - The aggregate response time of completed requests.
  • esErrorStatistics - Information about requests that failed with a 4xx Client Error status code.
  • esTotalCount - The total number of completed requests.

esFaultStatistics :: Lens' EdgeStatistics (Maybe FaultStatistics) Source #

Information about requests that failed with a 5xx Server Error status code.

esOKCount :: Lens' EdgeStatistics (Maybe Integer) Source #

The number of requests that completed with a 2xx Success status code.

esTotalResponseTime :: Lens' EdgeStatistics (Maybe Double) Source #

The aggregate response time of completed requests.

esErrorStatistics :: Lens' EdgeStatistics (Maybe ErrorStatistics) Source #

Information about requests that failed with a 4xx Client Error status code.

esTotalCount :: Lens' EdgeStatistics (Maybe Integer) Source #

The total number of completed requests.

EncryptionConfig

data EncryptionConfig Source #

A configuration document that specifies encryption configuration settings.

See: encryptionConfig smart constructor.

Instances
Eq EncryptionConfig Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data EncryptionConfig Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: EncryptionConfig -> Constr #

dataTypeOf :: EncryptionConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Read EncryptionConfig Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show EncryptionConfig Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic EncryptionConfig Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep EncryptionConfig :: Type -> Type #

Hashable EncryptionConfig Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON EncryptionConfig Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData EncryptionConfig Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: EncryptionConfig -> () #

type Rep EncryptionConfig Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep EncryptionConfig = D1 (MetaData "EncryptionConfig" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "EncryptionConfig'" PrefixI True) (S1 (MetaSel (Just "_ecStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EncryptionStatus)) :*: (S1 (MetaSel (Just "_ecKeyId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ecType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EncryptionType)))))

encryptionConfig :: EncryptionConfig Source #

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

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

  • ecStatus - The encryption status. After modifying encryption configuration with PutEncryptionConfig , the status can be UPDATING for up to one hour before X-Ray starts encrypting data with the new key.
  • ecKeyId - The ID of the customer master key (CMK) used for encryption, if applicable.
  • ecType - The type of encryption. Set to KMS for encryption with CMKs. Set to NONE for default encryption.

ecStatus :: Lens' EncryptionConfig (Maybe EncryptionStatus) Source #

The encryption status. After modifying encryption configuration with PutEncryptionConfig , the status can be UPDATING for up to one hour before X-Ray starts encrypting data with the new key.

ecKeyId :: Lens' EncryptionConfig (Maybe Text) Source #

The ID of the customer master key (CMK) used for encryption, if applicable.

ecType :: Lens' EncryptionConfig (Maybe EncryptionType) Source #

The type of encryption. Set to KMS for encryption with CMKs. Set to NONE for default encryption.

ErrorStatistics

data ErrorStatistics Source #

Information about requests that failed with a 4xx Client Error status code.

See: errorStatistics smart constructor.

Instances
Eq ErrorStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data ErrorStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: ErrorStatistics -> Constr #

dataTypeOf :: ErrorStatistics -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ErrorStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show ErrorStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic ErrorStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep ErrorStatistics :: Type -> Type #

Hashable ErrorStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON ErrorStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData ErrorStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: ErrorStatistics -> () #

type Rep ErrorStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep ErrorStatistics = D1 (MetaData "ErrorStatistics" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "ErrorStatistics'" PrefixI True) (S1 (MetaSel (Just "_eOtherCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: (S1 (MetaSel (Just "_eThrottleCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: S1 (MetaSel (Just "_eTotalCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)))))

errorStatistics :: ErrorStatistics Source #

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

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

  • eOtherCount - The number of requests that failed with untracked 4xx Client Error status codes.
  • eThrottleCount - The number of requests that failed with a 419 throttling status code.
  • eTotalCount - The total number of requests that failed with a 4xx Client Error status code.

eOtherCount :: Lens' ErrorStatistics (Maybe Integer) Source #

The number of requests that failed with untracked 4xx Client Error status codes.

eThrottleCount :: Lens' ErrorStatistics (Maybe Integer) Source #

The number of requests that failed with a 419 throttling status code.

eTotalCount :: Lens' ErrorStatistics (Maybe Integer) Source #

The total number of requests that failed with a 4xx Client Error status code.

FaultStatistics

data FaultStatistics Source #

Information about requests that failed with a 5xx Server Error status code.

See: faultStatistics smart constructor.

Instances
Eq FaultStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data FaultStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: FaultStatistics -> Constr #

dataTypeOf :: FaultStatistics -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FaultStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show FaultStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic FaultStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep FaultStatistics :: Type -> Type #

Hashable FaultStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON FaultStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData FaultStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: FaultStatistics -> () #

type Rep FaultStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep FaultStatistics = D1 (MetaData "FaultStatistics" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "FaultStatistics'" PrefixI True) (S1 (MetaSel (Just "_fsOtherCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: S1 (MetaSel (Just "_fsTotalCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))))

faultStatistics :: FaultStatistics Source #

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

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

  • fsOtherCount - The number of requests that failed with untracked 5xx Server Error status codes.
  • fsTotalCount - The total number of requests that failed with a 5xx Server Error status code.

fsOtherCount :: Lens' FaultStatistics (Maybe Integer) Source #

The number of requests that failed with untracked 5xx Server Error status codes.

fsTotalCount :: Lens' FaultStatistics (Maybe Integer) Source #

The total number of requests that failed with a 5xx Server Error status code.

HTTP

data HTTP Source #

Information about an HTTP request.

See: hTTP smart constructor.

Instances
Eq HTTP Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

Data HTTP Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: HTTP -> Constr #

dataTypeOf :: HTTP -> DataType #

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

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

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

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

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

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

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

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

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

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

Read HTTP Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show HTTP Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

showsPrec :: Int -> HTTP -> ShowS #

show :: HTTP -> String #

showList :: [HTTP] -> ShowS #

Generic HTTP Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep HTTP :: Type -> Type #

Methods

from :: HTTP -> Rep HTTP x #

to :: Rep HTTP x -> HTTP #

Hashable HTTP Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

hashWithSalt :: Int -> HTTP -> Int #

hash :: HTTP -> Int #

FromJSON HTTP Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData HTTP Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: HTTP -> () #

type Rep HTTP Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep HTTP = D1 (MetaData "HTTP" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "HTTP'" PrefixI True) ((S1 (MetaSel (Just "_httpHTTPMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_httpHTTPStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) :*: (S1 (MetaSel (Just "_httpClientIP") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_httpUserAgent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_httpHTTPURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

hTTP :: HTTP Source #

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

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

httpHTTPMethod :: Lens' HTTP (Maybe Text) Source #

The request method.

httpHTTPStatus :: Lens' HTTP (Maybe Int) Source #

The response status.

httpClientIP :: Lens' HTTP (Maybe Text) Source #

The IP address of the requestor.

httpUserAgent :: Lens' HTTP (Maybe Text) Source #

The request's user agent string.

httpHTTPURL :: Lens' HTTP (Maybe Text) Source #

The request URL.

HistogramEntry

data HistogramEntry Source #

An entry in a histogram for a statistic. A histogram maps the range of observed values on the X axis, and the prevalence of each value on the Y axis.

See: histogramEntry smart constructor.

Instances
Eq HistogramEntry Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data HistogramEntry Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: HistogramEntry -> Constr #

dataTypeOf :: HistogramEntry -> DataType #

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

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

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

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

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

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

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

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

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

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

Read HistogramEntry Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show HistogramEntry Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic HistogramEntry Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep HistogramEntry :: Type -> Type #

Hashable HistogramEntry Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON HistogramEntry Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData HistogramEntry Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: HistogramEntry -> () #

type Rep HistogramEntry Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep HistogramEntry = D1 (MetaData "HistogramEntry" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "HistogramEntry'" PrefixI True) (S1 (MetaSel (Just "_heCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_heValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double))))

histogramEntry :: HistogramEntry Source #

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

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

  • heCount - The prevalence of the entry.
  • heValue - The value of the entry.

heCount :: Lens' HistogramEntry (Maybe Int) Source #

The prevalence of the entry.

heValue :: Lens' HistogramEntry (Maybe Double) Source #

The value of the entry.

Segment

data Segment Source #

A segment from a trace that has been ingested by the X-Ray service. The segment can be compiled from documents uploaded with PutTraceSegments , or an inferred segment for a downstream service, generated from a subsegment sent by the service that called it.

For the full segment document schema, see AWS X-Ray Segment Documents in the AWS X-Ray Developer Guide .

See: segment smart constructor.

Instances
Eq Segment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

Data Segment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: Segment -> Constr #

dataTypeOf :: Segment -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Segment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show Segment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic Segment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep Segment :: Type -> Type #

Methods

from :: Segment -> Rep Segment x #

to :: Rep Segment x -> Segment #

Hashable Segment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

hashWithSalt :: Int -> Segment -> Int #

hash :: Segment -> Int #

FromJSON Segment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData Segment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: Segment -> () #

type Rep Segment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep Segment = D1 (MetaData "Segment" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "Segment'" PrefixI True) (S1 (MetaSel (Just "_sDocument") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_sId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

segment :: Segment Source #

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

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

sDocument :: Lens' Segment (Maybe Text) Source #

The segment document.

sId :: Lens' Segment (Maybe Text) Source #

The segment's ID.

ServiceId

data ServiceId Source #

See: serviceId smart constructor.

Instances
Eq ServiceId Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data ServiceId Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: ServiceId -> Constr #

dataTypeOf :: ServiceId -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ServiceId Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show ServiceId Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic ServiceId Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep ServiceId :: Type -> Type #

Hashable ServiceId Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON ServiceId Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData ServiceId Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: ServiceId -> () #

type Rep ServiceId Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep ServiceId = D1 (MetaData "ServiceId" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "ServiceId'" PrefixI True) ((S1 (MetaSel (Just "_siAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_siNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) :*: (S1 (MetaSel (Just "_siName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_siType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

serviceId :: ServiceId Source #

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

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

ServiceInfo

data ServiceInfo Source #

Information about an application that processed requests, users that made requests, or downstream services, resources and applications that an application used.

See: serviceInfo smart constructor.

Instances
Eq ServiceInfo Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data ServiceInfo Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: ServiceInfo -> Constr #

dataTypeOf :: ServiceInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ServiceInfo Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show ServiceInfo Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic ServiceInfo Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep ServiceInfo :: Type -> Type #

Hashable ServiceInfo Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON ServiceInfo Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData ServiceInfo Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: ServiceInfo -> () #

type Rep ServiceInfo Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep ServiceInfo = D1 (MetaData "ServiceInfo" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "ServiceInfo'" PrefixI True) (((S1 (MetaSel (Just "_sState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_sStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: S1 (MetaSel (Just "_sRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) :*: (S1 (MetaSel (Just "_sResponseTimeHistogram") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [HistogramEntry])) :*: (S1 (MetaSel (Just "_sDurationHistogram") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [HistogramEntry])) :*: S1 (MetaSel (Just "_sReferenceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))) :*: ((S1 (MetaSel (Just "_sAccountId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_sNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "_sName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_sEndTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: S1 (MetaSel (Just "_sType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_sEdges") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Edge])) :*: S1 (MetaSel (Just "_sSummaryStatistics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ServiceStatistics)))))))

serviceInfo :: ServiceInfo Source #

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

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

  • sState - The service's state.
  • sStartTime - The start time of the first segment that the service generated.
  • sRoot - Indicates that the service was the first service to process a request.
  • sResponseTimeHistogram - A histogram that maps the spread of service response times.
  • sDurationHistogram - A histogram that maps the spread of service durations.
  • sReferenceId - Identifier for the service. Unique within the service map.
  • sAccountId - Identifier of the AWS account in which the service runs.
  • sNames - A list of names for the service, including the canonical name.
  • sName - The canonical name of the service.
  • sEndTime - The end time of the last segment that the service generated.
  • sType - The type of service. * AWS Resource - The type of an AWS resource. For example, AWS::EC2::Instance for a application running on Amazon EC2 or AWS::DynamoDB::Table for an Amazon DynamoDB table that the application used. * AWS Service - The type of an AWS service. For example, AWS::DynamoDB for downstream calls to Amazon DynamoDB that didn't target a specific table. * client - Represents the clients that sent requests to a root service. * remote - A downstream service of indeterminate type.
  • sEdges - Connections to downstream services.
  • sSummaryStatistics - Aggregated statistics for the service.

sState :: Lens' ServiceInfo (Maybe Text) Source #

The service's state.

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

The start time of the first segment that the service generated.

sRoot :: Lens' ServiceInfo (Maybe Bool) Source #

Indicates that the service was the first service to process a request.

sResponseTimeHistogram :: Lens' ServiceInfo [HistogramEntry] Source #

A histogram that maps the spread of service response times.

sDurationHistogram :: Lens' ServiceInfo [HistogramEntry] Source #

A histogram that maps the spread of service durations.

sReferenceId :: Lens' ServiceInfo (Maybe Int) Source #

Identifier for the service. Unique within the service map.

sAccountId :: Lens' ServiceInfo (Maybe Text) Source #

Identifier of the AWS account in which the service runs.

sNames :: Lens' ServiceInfo [Text] Source #

A list of names for the service, including the canonical name.

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

The canonical name of the service.

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

The end time of the last segment that the service generated.

sType :: Lens' ServiceInfo (Maybe Text) Source #

The type of service. * AWS Resource - The type of an AWS resource. For example, AWS::EC2::Instance for a application running on Amazon EC2 or AWS::DynamoDB::Table for an Amazon DynamoDB table that the application used. * AWS Service - The type of an AWS service. For example, AWS::DynamoDB for downstream calls to Amazon DynamoDB that didn't target a specific table. * client - Represents the clients that sent requests to a root service. * remote - A downstream service of indeterminate type.

sEdges :: Lens' ServiceInfo [Edge] Source #

Connections to downstream services.

sSummaryStatistics :: Lens' ServiceInfo (Maybe ServiceStatistics) Source #

Aggregated statistics for the service.

ServiceStatistics

data ServiceStatistics Source #

Response statistics for a service.

See: serviceStatistics smart constructor.

Instances
Eq ServiceStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data ServiceStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: ServiceStatistics -> Constr #

dataTypeOf :: ServiceStatistics -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ServiceStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show ServiceStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic ServiceStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep ServiceStatistics :: Type -> Type #

Hashable ServiceStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON ServiceStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData ServiceStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: ServiceStatistics -> () #

type Rep ServiceStatistics Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep ServiceStatistics = D1 (MetaData "ServiceStatistics" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "ServiceStatistics'" PrefixI True) ((S1 (MetaSel (Just "_ssFaultStatistics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FaultStatistics)) :*: S1 (MetaSel (Just "_ssOKCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))) :*: (S1 (MetaSel (Just "_ssTotalResponseTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double)) :*: (S1 (MetaSel (Just "_ssErrorStatistics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ErrorStatistics)) :*: S1 (MetaSel (Just "_ssTotalCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))))))

serviceStatistics :: ServiceStatistics Source #

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

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

  • ssFaultStatistics - Information about requests that failed with a 5xx Server Error status code.
  • ssOKCount - The number of requests that completed with a 2xx Success status code.
  • ssTotalResponseTime - The aggregate response time of completed requests.
  • ssErrorStatistics - Information about requests that failed with a 4xx Client Error status code.
  • ssTotalCount - The total number of completed requests.

ssFaultStatistics :: Lens' ServiceStatistics (Maybe FaultStatistics) Source #

Information about requests that failed with a 5xx Server Error status code.

ssOKCount :: Lens' ServiceStatistics (Maybe Integer) Source #

The number of requests that completed with a 2xx Success status code.

ssTotalResponseTime :: Lens' ServiceStatistics (Maybe Double) Source #

The aggregate response time of completed requests.

ssErrorStatistics :: Lens' ServiceStatistics (Maybe ErrorStatistics) Source #

Information about requests that failed with a 4xx Client Error status code.

ssTotalCount :: Lens' ServiceStatistics (Maybe Integer) Source #

The total number of completed requests.

TelemetryRecord

data TelemetryRecord Source #

See: telemetryRecord smart constructor.

Instances
Eq TelemetryRecord Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data TelemetryRecord Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: TelemetryRecord -> Constr #

dataTypeOf :: TelemetryRecord -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TelemetryRecord Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show TelemetryRecord Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic TelemetryRecord Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep TelemetryRecord :: Type -> Type #

Hashable TelemetryRecord Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

ToJSON TelemetryRecord Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData TelemetryRecord Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: TelemetryRecord -> () #

type Rep TelemetryRecord Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep TelemetryRecord = D1 (MetaData "TelemetryRecord" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "TelemetryRecord'" PrefixI True) ((S1 (MetaSel (Just "_trSegmentsReceivedCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 (MetaSel (Just "_trSegmentsSentCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "_trSegmentsSpilloverCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))) :*: (S1 (MetaSel (Just "_trSegmentsRejectedCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 (MetaSel (Just "_trBackendConnectionErrors") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BackendConnectionErrors)) :*: S1 (MetaSel (Just "_trTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 POSIX)))))

telemetryRecord Source #

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

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

Trace

data Trace Source #

A collection of segment documents with matching trace IDs.

See: trace smart constructor.

Instances
Eq Trace Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

Data Trace Source # 
Instance details

Defined in Network.AWS.XRay.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 #

Read Trace Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show Trace Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

showsPrec :: Int -> Trace -> ShowS #

show :: Trace -> String #

showList :: [Trace] -> ShowS #

Generic Trace Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep Trace :: Type -> Type #

Methods

from :: Trace -> Rep Trace x #

to :: Rep Trace x -> Trace #

Hashable Trace Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

hashWithSalt :: Int -> Trace -> Int #

hash :: Trace -> Int #

FromJSON Trace Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData Trace Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: Trace -> () #

type Rep Trace Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep Trace = D1 (MetaData "Trace" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "Trace'" PrefixI True) (S1 (MetaSel (Just "_tId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_tSegments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Segment])) :*: S1 (MetaSel (Just "_tDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double)))))

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:

  • tId - The unique identifier for the request that generated the trace's segments and subsegments.
  • tSegments - Segment documents for the segments and subsegments that comprise the trace.
  • tDuration - The length of time in seconds between the start time of the root segment and the end time of the last segment that completed.

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

The unique identifier for the request that generated the trace's segments and subsegments.

tSegments :: Lens' Trace [Segment] Source #

Segment documents for the segments and subsegments that comprise the trace.

tDuration :: Lens' Trace (Maybe Double) Source #

The length of time in seconds between the start time of the root segment and the end time of the last segment that completed.

TraceSummary

data TraceSummary Source #

Metadata generated from the segment documents in a trace.

See: traceSummary smart constructor.

Instances
Eq TraceSummary Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data TraceSummary Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: TraceSummary -> Constr #

dataTypeOf :: TraceSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TraceSummary Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show TraceSummary Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic TraceSummary Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep TraceSummary :: Type -> Type #

Hashable TraceSummary Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON TraceSummary Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData TraceSummary Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: TraceSummary -> () #

type Rep TraceSummary Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

traceSummary :: TraceSummary Source #

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

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

  • tsAnnotations - Annotations from the trace's segment documents.
  • tsHasThrottle - One or more of the segment documents has a 429 throttling error.
  • tsUsers - Users from the trace's segment documents.
  • tsHasFault - One or more of the segment documents has a 500 series error.
  • tsServiceIds - Service IDs from the trace's segment documents.
  • tsIsPartial - One or more of the segment documents is in progress.
  • tsHasError - One or more of the segment documents has a 400 series error.
  • tsId - The unique identifier for the request that generated the trace's segments and subsegments.
  • tsHTTP - Information about the HTTP request served by the trace.
  • tsDuration - The length of time in seconds between the start time of the root segment and the end time of the last segment that completed.
  • tsResponseTime - The length of time in seconds between the start and end times of the root segment. If the service performs work asynchronously, the response time measures the time before the response is sent to the user, while the duration measures the amount of time before the last traced activity completes.

tsAnnotations :: Lens' TraceSummary (HashMap Text [ValueWithServiceIds]) Source #

Annotations from the trace's segment documents.

tsHasThrottle :: Lens' TraceSummary (Maybe Bool) Source #

One or more of the segment documents has a 429 throttling error.

tsUsers :: Lens' TraceSummary [TraceUser] Source #

Users from the trace's segment documents.

tsHasFault :: Lens' TraceSummary (Maybe Bool) Source #

One or more of the segment documents has a 500 series error.

tsServiceIds :: Lens' TraceSummary [ServiceId] Source #

Service IDs from the trace's segment documents.

tsIsPartial :: Lens' TraceSummary (Maybe Bool) Source #

One or more of the segment documents is in progress.

tsHasError :: Lens' TraceSummary (Maybe Bool) Source #

One or more of the segment documents has a 400 series error.

tsId :: Lens' TraceSummary (Maybe Text) Source #

The unique identifier for the request that generated the trace's segments and subsegments.

tsHTTP :: Lens' TraceSummary (Maybe HTTP) Source #

Information about the HTTP request served by the trace.

tsDuration :: Lens' TraceSummary (Maybe Double) Source #

The length of time in seconds between the start time of the root segment and the end time of the last segment that completed.

tsResponseTime :: Lens' TraceSummary (Maybe Double) Source #

The length of time in seconds between the start and end times of the root segment. If the service performs work asynchronously, the response time measures the time before the response is sent to the user, while the duration measures the amount of time before the last traced activity completes.

TraceUser

data TraceUser Source #

Information about a user recorded in segment documents.

See: traceUser smart constructor.

Instances
Eq TraceUser Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data TraceUser Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: TraceUser -> Constr #

dataTypeOf :: TraceUser -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TraceUser Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show TraceUser Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic TraceUser Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep TraceUser :: Type -> Type #

Hashable TraceUser Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON TraceUser Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData TraceUser Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: TraceUser -> () #

type Rep TraceUser Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep TraceUser = D1 (MetaData "TraceUser" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "TraceUser'" PrefixI True) (S1 (MetaSel (Just "_tuServiceIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ServiceId])) :*: S1 (MetaSel (Just "_tuUserName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

traceUser :: TraceUser Source #

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

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

tuServiceIds :: Lens' TraceUser [ServiceId] Source #

Services that the user's request hit.

tuUserName :: Lens' TraceUser (Maybe Text) Source #

The user's name.

UnprocessedTraceSegment

data UnprocessedTraceSegment Source #

Information about a segment that failed processing.

See: unprocessedTraceSegment smart constructor.

Instances
Eq UnprocessedTraceSegment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data UnprocessedTraceSegment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: UnprocessedTraceSegment -> Constr #

dataTypeOf :: UnprocessedTraceSegment -> DataType #

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

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

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

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

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

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

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

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

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

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

Read UnprocessedTraceSegment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show UnprocessedTraceSegment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic UnprocessedTraceSegment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep UnprocessedTraceSegment :: Type -> Type #

Hashable UnprocessedTraceSegment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON UnprocessedTraceSegment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData UnprocessedTraceSegment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: UnprocessedTraceSegment -> () #

type Rep UnprocessedTraceSegment Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep UnprocessedTraceSegment = D1 (MetaData "UnprocessedTraceSegment" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "UnprocessedTraceSegment'" PrefixI True) (S1 (MetaSel (Just "_utsErrorCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_utsId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_utsMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

unprocessedTraceSegment :: UnprocessedTraceSegment Source #

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

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

utsErrorCode :: Lens' UnprocessedTraceSegment (Maybe Text) Source #

The error that caused processing to fail.

ValueWithServiceIds

data ValueWithServiceIds Source #

Information about a segment annotation.

See: valueWithServiceIds smart constructor.

Instances
Eq ValueWithServiceIds Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Data ValueWithServiceIds Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

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

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

toConstr :: ValueWithServiceIds -> Constr #

dataTypeOf :: ValueWithServiceIds -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ValueWithServiceIds Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Show ValueWithServiceIds Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Generic ValueWithServiceIds Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Associated Types

type Rep ValueWithServiceIds :: Type -> Type #

Hashable ValueWithServiceIds Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

FromJSON ValueWithServiceIds Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

NFData ValueWithServiceIds Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

Methods

rnf :: ValueWithServiceIds -> () #

type Rep ValueWithServiceIds Source # 
Instance details

Defined in Network.AWS.XRay.Types.Product

type Rep ValueWithServiceIds = D1 (MetaData "ValueWithServiceIds" "Network.AWS.XRay.Types.Product" "amazonka-xray-1.6.1-6uyA4HRXo0kJ9ryfmHEerX" False) (C1 (MetaCons "ValueWithServiceIds'" PrefixI True) (S1 (MetaSel (Just "_vwsiServiceIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ServiceId])) :*: S1 (MetaSel (Just "_vwsiAnnotationValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AnnotationValue))))

valueWithServiceIds :: ValueWithServiceIds Source #

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

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

vwsiServiceIds :: Lens' ValueWithServiceIds [ServiceId] Source #

Services to which the annotation applies.