Skip to content

Commit

Permalink
Removed HashMap from logRecordExporterExport and updated tests
Browse files Browse the repository at this point in the history
  • Loading branch information
evanlauer1 committed Jul 15, 2024
1 parent 72189e2 commit 3a0df02
Show file tree
Hide file tree
Showing 2 changed files with 7 additions and 13 deletions.
7 changes: 2 additions & 5 deletions sdk/src/OpenTelemetry/LogRecordProcessor/Simple.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,6 @@ import Control.Concurrent.Async (async, cancel)
import Control.Concurrent.Chan.Unagi
import Control.Exception
import Control.Monad (forever)
import qualified Data.HashMap.Strict as H
import qualified Data.Vector as V
import OpenTelemetry.Internal.Common.Types
import OpenTelemetry.Internal.Logs.Types
Expand All @@ -26,7 +25,7 @@ simpleProcessor LogRecordExporter {..} = do
bracketOnError
(readChan outChan)
(writeChan inChan)
exportSingleLogRecord
(logRecordExporterExport . V.singleton)

let logRecordProcessorForceFlush =
( do
Expand Down Expand Up @@ -60,7 +59,5 @@ simpleProcessor LogRecordExporter {..} = do
case mlr of
Nothing -> pure acc
Just lr -> do
res <- exportSingleLogRecord lr
res <- logRecordExporterExport $ V.singleton lr
forceFlushOutChan outChan (res : acc)

exportSingleLogRecord = logRecordExporterExport . (H.singleton <$> readLogRecordInstrumentationScope <*> V.singleton)
13 changes: 5 additions & 8 deletions sdk/test/OpenTelemetry/LogRecordProcessorSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@

module OpenTelemetry.LogRecordProcessorSpec where

import qualified Data.HashMap.Strict as H
import Data.IORef
import qualified Data.Vector as V
import qualified OpenTelemetry.Context as Context
Expand All @@ -22,13 +21,12 @@ getTestExporter = do
numExportsRef <- newIORef 0
shutdownRef <- newIORef False

let logRecordExporterExport logRecordsByLibrary = do
let logRecordExporterExport logRecords = do
shutdown <- readIORef shutdownRef
if shutdown
then pure (Failure Nothing)
else do
let numLogRecords = foldr (\lrs n -> n + V.length lrs) 0 logRecordsByLibrary
modifyIORef numExportsRef (+ numLogRecords)
modifyIORef numExportsRef $ (+) $ V.length logRecords

pure Success

Expand All @@ -52,9 +50,8 @@ getTestExporterWithoutShutdown :: IO (IORef Int, LogRecordExporter body)
getTestExporterWithoutShutdown = do
numExportsRef <- newIORef 0

let logRecordExporterExport logRecordsByLibrary = do
let numLogRecords = foldr (\lrs n -> n + V.length lrs) 0 logRecordsByLibrary
modifyIORef numExportsRef (+ numLogRecords)
let logRecordExporterExport logRecords = do
modifyIORef numExportsRef $ (+) $ V.length $ logRecords

pure Success

Expand Down Expand Up @@ -110,7 +107,7 @@ spec = describe "LogRecordProcessor" $ do
numExports <- readIORef numExportsRef
numExports `shouldBe` 3

exportRes <- logRecordExporterExport testExporter H.empty
exportRes <- logRecordExporterExport testExporter V.empty
exportRes `shouldSatisfy` \case
Success -> False
Failure _ -> True
Expand Down

0 comments on commit 3a0df02

Please sign in to comment.