| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Network.AWS.XRayClient.WAI
Description
Module for using a WAI Middleware as an X-Ray client
Synopsis
- data XRayClientConfig = XRayClientConfig {
- xrayClientConfigDaemonHost :: !Text
- xrayClientConfigDaemonPort :: !Int
- xrayClientConfigApplicationName :: !Text
- xrayClientConfigSampler :: !(Maybe (Request -> Response -> POSIXTime -> POSIXTime -> IO Bool))
- xrayClientConfig :: Text -> XRayClientConfig
- xrayTraceMiddleware :: XRayClientConfig -> Middleware
- newtype NoAddressInfoException = NoAddressInfoException String
- xrayWaiVaultKey :: Key XRayVaultData
- vaultDataFromRequest :: Request -> Maybe XRayVaultData
- data XRayVaultData = XRayVaultData {}
- traceXRaySubsegment :: MonadUnliftIO m => Request -> Text -> (XRaySegment -> XRaySegment) -> m a -> m a
- traceXRaySubsegment' :: MonadUnliftIO m => XRayVaultData -> Text -> (XRaySegment -> XRaySegment) -> m a -> m a
- atomicallyAddVaultDataSubsegment :: XRayVaultData -> XRaySegment -> IO ()
- makeSubsegmentIndependent :: XRayVaultData -> XRaySegment -> XRaySegment
- module Network.AWS.XRayClient.TraceId
- module Network.AWS.XRayClient.SendSegments
- module Network.AWS.XRayClient.Segment
Documentation
data XRayClientConfig Source #
Configuration type for the XRay client middleware.
Constructors
| XRayClientConfig | |
Fields
| |
xrayClientConfig :: Text -> XRayClientConfig Source #
Constructor for XRayClientConfig with required arguments.
xrayTraceMiddleware :: XRayClientConfig -> Middleware Source #
Traces the execution time of a request and sends the the local X-Ray daemon.
newtype NoAddressInfoException #
Constructors
| NoAddressInfoException String |
Instances
| Show NoAddressInfoException | |
Defined in Network.AWS.XRayClient.SendSegments Methods showsPrec :: Int -> NoAddressInfoException -> ShowS # show :: NoAddressInfoException -> String # showList :: [NoAddressInfoException] -> ShowS # | |
| Exception NoAddressInfoException | |
Defined in Network.AWS.XRayClient.SendSegments | |
xrayWaiVaultKey :: Key XRayVaultData Source #
This is a Key for the vault inside each WAI Request. It is used to
get to the XRayVaultData for the current request.
vaultDataFromRequest :: Request -> Maybe XRayVaultData Source #
Try to get XRayVaultData from the WAI Request vault.
data XRayVaultData Source #
We use the WAI Vault to store data needed during traces.
Constructors
| XRayVaultData | |
Fields
| |
traceXRaySubsegment :: MonadUnliftIO m => Request -> Text -> (XRaySegment -> XRaySegment) -> m a -> m a Source #
Time a MonadIO action and add it to the list of subsegments.
traceXRaySubsegment' :: MonadUnliftIO m => XRayVaultData -> Text -> (XRaySegment -> XRaySegment) -> m a -> m a Source #
atomicallyAddVaultDataSubsegment :: XRayVaultData -> XRaySegment -> IO () Source #
Add subsegment to XRay vault data IORef.
makeSubsegmentIndependent :: XRayVaultData -> XRaySegment -> XRaySegment Source #
Uses the trace ID and segment ID of the root segment from the vault to make a subsegment independent. This is useful so nested components that create subsegments don't need all of this information threaded down to them. We can just decorate all of the subsegments with it before sending them off.