Skip to content

Commit

Permalink
Added LogRecordExporters and updated documentation.
Browse files Browse the repository at this point in the history
  • Loading branch information
evanlauer1 committed Jul 22, 2024
1 parent 1607ed1 commit c648616
Show file tree
Hide file tree
Showing 3 changed files with 83 additions and 14 deletions.
8 changes: 7 additions & 1 deletion api/src/OpenTelemetry/Exporter/LogRecord.hs
Original file line number Diff line number Diff line change
@@ -1,2 +1,8 @@
module OpenTelemetry.Exporter.LogRecord () where
module OpenTelemetry.Exporter.LogRecord (
LogRecordExporter (..),
ShutdownResult (..),
) where

import OpenTelemetry.Internal.Logs.Types (LogRecordExporter (..))
import OpenTelemetry.Processor.LogRecord (ShutdownResult (..))

78 changes: 76 additions & 2 deletions api/src/OpenTelemetry/Internal/Logs/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
{-# LANGUAGE NamedFieldPuns #-}

module OpenTelemetry.Internal.Logs.Types (
LogRecordExporter (..),
LogRecordProcessor (..),
LoggerProvider (..),
Logger (..),
Expand All @@ -21,18 +22,91 @@ module OpenTelemetry.Internal.Logs.Types (

import Control.Concurrent.Async
import Data.Function (on)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as H
import Data.IORef (IORef, atomicModifyIORef, modifyIORef, newIORef, readIORef)
import Data.Text (Text)
import Data.Vector (Vector)
import OpenTelemetry.Common (Timestamp, TraceFlags)
import OpenTelemetry.Context.Types (Context)
import OpenTelemetry.Internal.Common.Types (InstrumentationLibrary, ShutdownResult)
import OpenTelemetry.Internal.Common.Types (ExportResult, InstrumentationLibrary, ShutdownResult)
import OpenTelemetry.Internal.Trace.Id (SpanId, TraceId)
import OpenTelemetry.LogAttributes
import OpenTelemetry.Resource (MaterializedResources)


{- | LogRecordExporter defines the interface that protocol-specific exporters must implement so that they can be plugged into OpenTelemetry SDK and support sending of telemetry data.
The goal of the interface is to minimize burden of implementation for protocol-dependent telemetry exporters. The protocol exporter is expected to be primarily a simple telemetry data encoder and transmitter.
-}
data LogRecordExporter body = LogRecordExporter
{ logRecordExporterExport :: HashMap InstrumentationLibrary (Vector ReadableLogRecord) -> IO ExportResult
-- ^ Exports a batch of ReadableLogRecords. Protocol exporters that will implement this function are typically expected to serialize
-- and transmit the data to the destination.
--
-- Export will never be called concurrently for the same exporter instance. Depending on the implementation the result of the export
-- may be returned to the Processor not in the return value of the call to Export but in a language specific way for signaling completion
-- of an asynchronous task. This means that while an instance of an exporter will never have it Export called concurrently it does not
-- mean that the task of exporting can not be done concurrently. How this is done is outside the scope of this specification.
-- Each implementation MUST document the concurrency characteristics the SDK requires of the exporter.
--
-- Export MUST NOT block indefinitely, there MUST be a reasonable upper limit after which the call must time out with an error result (Failure).
--
-- Concurrent requests and retry logic is the responsibility of the exporter. The default SDK’s LogRecordProcessors SHOULD NOT implement
-- retry logic, as the required logic is likely to depend heavily on the specific protocol and backend the logs are being sent to.
-- For example, the OpenTelemetry Protocol (OTLP) specification defines logic for both sending concurrent requests and retrying requests.
--
-- Result:
-- Success - The batch has been successfully exported. For protocol exporters this typically means that the data is sent over the wire and delivered to the destination server.
-- Failure - exporting failed. The batch must be dropped. For example, this can happen when the batch contains bad data and cannot be serialized.
, logRecordExporterForceFlush :: IO ()
-- ^ This is a hint to ensure that the export of any ReadableLogRecords the exporter has received prior to the call to ForceFlush SHOULD
-- be completed as soon as possible, preferably before returning from this method.
--
-- ForceFlush SHOULD provide a way to let the caller know whether it succeeded, failed or timed out.
--
-- ForceFlush SHOULD only be called in cases where it is absolutely necessary, such as when using some FaaS providers that may suspend
-- the process after an invocation, but before the exporter exports the ReadlableLogRecords.
--
-- ForceFlush SHOULD complete or abort within some timeout. ForceFlush can be implemented as a blocking API or an asynchronous API which
-- notifies the caller via a callback or an event. OpenTelemetry SDK authors MAY decide if they want to make the flush timeout configurable.
, logRecordExporterShutdown :: IO ()
-- ^
-- Shuts down the exporter. Called when SDK is shut down. This is an opportunity for exporter to do any cleanup required.
--
-- Shutdown SHOULD be called only once for each LogRecordExporter instance. After the call to Shutdown subsequent calls to Export are not
-- allowed and SHOULD return a Failure result.
--
-- Shutdown SHOULD NOT block indefinitely (e.g. if it attempts to flush the data and the destination is unavailable).
-- OpenTelemetry SDK authors MAY decide if they want to make the shutdown timeout configurable.
}


{- | LogRecordProcessor is an interface which allows hooks for LogRecord emitting.
Built-in processors are responsible for batching and conversion of LogRecords to exportable representation and passing batches to exporters.
LogRecordProcessors can be registered directly on SDK LoggerProvider and they are invoked in the same order as they were registered.
Each processor registered on LoggerProvider is part of a pipeline that consists of a processor and optional exporter. The SDK MUST allow each pipeline to end with an individual exporter.
The SDK MUST allow users to implement and configure custom processors and decorate built-in processors for advanced scenarios such as enriching with attributes.
The following diagram shows LogRecordProcessor’s relationship to other components in the SDK:
+-----+------------------------+ +------------------------------+ +-------------------------+
| | | | | | |
| | | | Batching LogRecordProcessor | | LogRecordExporter |
| | +---> Simple LogRecordProcessor +---> (OtlpExporter) |
| | | | | | |
| SDK | Logger.emit(LogRecord) | +------------------------------+ +-------------------------+
| | |
| | |
| | |
| | |
| | |
+-----+------------------------+
-}
data LogRecordProcessor = LogRecordProcessor
{ logRecordProcessorOnEmit :: ReadWriteLogRecord -> Context -> IO ()
-- ^ Called when a LogRecord is emitted. This method is called synchronously on the thread that emitted the LogRecord, therefore it SHOULD NOT block or throw exceptions.
Expand Down Expand Up @@ -250,7 +324,7 @@ data LogRecordArguments = LogRecordArguments
, severityText :: Maybe Text
, severityNumber :: Maybe SeverityNumber
, body :: AnyValue
, attributes :: H.HashMap Text AnyValue
, attributes :: HashMap Text AnyValue
}


Expand Down
11 changes: 0 additions & 11 deletions api/src/OpenTelemetry/Processor/LogRecord.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,3 @@
{- |
@LogRecordProcessor@ is an interface which allows hooks for @LogRecord@ emit method invocations.
Built-in log processors are responsible for batching and conversion of spans to exportable representation and passing batches to exporters.
Log processors can be registered directly on SDK LoggerProvider and they are invoked in the same order as they were registered.
Each processor registered on LoggerProvider is a start of pipeline that consist of log processor and optional exporter. SDK MUST allow to end each pipeline with individual exporter.
SDK MUST allow users to implement and configure custom processors and decorate built-in processors for advanced scenarios such as tagging or filtering.
-}
module OpenTelemetry.Processor.LogRecord (
LogRecordProcessor (..),
ShutdownResult (..),
Expand Down

0 comments on commit c648616

Please sign in to comment.