Skip to content

Commit 9bbdfa8

Browse files
committed
Fix warnings and formatting
1 parent 972a5fe commit 9bbdfa8

File tree

10 files changed

+270
-247
lines changed

10 files changed

+270
-247
lines changed

opentelemetry-extra/exe/eventlog-summary/Main.hs

+18-17
Original file line numberDiff line numberDiff line change
@@ -4,20 +4,20 @@
44
module Main where
55

66
import Control.Monad
7-
import qualified Data.Text as T
87
import qualified Data.ByteString.Char8 as B8
9-
import OpenTelemetry.Common
10-
import OpenTelemetry.EventlogStreaming_Internal
11-
import System.Environment
128
import Data.Char (isDigit)
139
import Data.Function
1410
import qualified Data.HashTable.IO as H
1511
import Data.IORef
1612
import Data.IntMap.Strict (IntMap)
1713
import qualified Data.IntMap.Strict as IntMap
1814
import Data.List (sortOn)
15+
import qualified Data.Text as T
1916
import Data.Word
2017
import Graphics.Vega.VegaLite hiding (name)
18+
import OpenTelemetry.Common
19+
import OpenTelemetry.EventlogStreaming_Internal
20+
import System.Environment
2121
import Text.Printf
2222

2323
type HashTable k v = H.BasicHashTable k v
@@ -69,17 +69,19 @@ main = do
6969
pure ExportSuccess
7070
)
7171
(pure ())
72-
metric_exporter <- aggregated $ Exporter
73-
( \metrics -> do
74-
forM_ metrics $ \(AggregatedMetric (CaptureInstrument _ name) (MetricDatapoint _ value)) ->
75-
modifyIORef metricStats $ \s -> case splitCapability (B8.unpack name) of
76-
(_, "threads") -> s { max_threads = max value (max_threads s) }
77-
(Just cap, "heap_alloc_bytes") -> s { total_alloc_bytes = IntMap.insert cap value (total_alloc_bytes s) }
78-
(_, "heap_live_bytes") -> s { max_live_bytes = max value (max_live_bytes s) }
79-
_ -> s
80-
pure ExportSuccess
81-
)
82-
(pure ())
72+
metric_exporter <-
73+
aggregated $
74+
Exporter
75+
( \metrics -> do
76+
forM_ metrics $ \(AggregatedMetric (CaptureInstrument _ name) (MetricDatapoint _ value)) ->
77+
modifyIORef metricStats $ \s -> case splitCapability (B8.unpack name) of
78+
(_, "threads") -> s {max_threads = max value (max_threads s)}
79+
(Just cap, "heap_alloc_bytes") -> s {total_alloc_bytes = IntMap.insert cap value (total_alloc_bytes s)}
80+
(_, "heap_live_bytes") -> s {max_live_bytes = max value (max_live_bytes s)}
81+
_ -> s
82+
pure ExportSuccess
83+
)
84+
(pure ())
8385
exportEventlog span_exporter metric_exporter path
8486
leaderboard <- sortOn (total_ns . snd) <$> H.toList opCounts
8587
printf "Count\tTot ms\tMin ms\tMax ms\tOperation\n"
@@ -109,8 +111,7 @@ main = do
109111

110112
putStrLn "---"
111113

112-
let
113-
vega_visualization =
114+
let vega_visualization =
114115
toVegaLite
115116
[ title "Total duration of operation" [],
116117
vega_dat,

opentelemetry-extra/exe/eventlog-to-zipkin/Main.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,8 @@
33
module Main where
44

55
import qualified Data.Text as T
6-
import OpenTelemetry.EventlogStreaming_Internal
76
import OpenTelemetry.Common
7+
import OpenTelemetry.EventlogStreaming_Internal
88
import OpenTelemetry.ZipkinExporter
99
import System.Environment (getArgs)
1010
import System.FilePath

opentelemetry-extra/src/OpenTelemetry/ChromeExporter.hs

+20-17
Original file line numberDiff line numberDiff line change
@@ -5,14 +5,14 @@ module OpenTelemetry.ChromeExporter where
55
import Control.Monad
66
import Data.Aeson
77
import qualified Data.ByteString.Lazy as LBS
8-
import qualified Data.Text.Encoding as TE
98
import Data.Function
109
import Data.HashMap.Strict as HM
1110
import Data.List (sortOn)
11+
import qualified Data.Text.Encoding as TE
1212
import Data.Word
1313
import OpenTelemetry.Common
14-
import System.IO
1514
import OpenTelemetry.EventlogStreaming_Internal
15+
import System.IO
1616

1717
newtype ChromeBeginSpan = ChromeBegin Span
1818

@@ -101,21 +101,24 @@ createChromeExporter' path doWeCollapseThreads = do
101101
hPutStrLn f "\n]"
102102
hClose f
103103
)
104-
metric_exporter <- aggregated $ Exporter
105-
( \metrics -> do
106-
-- forM_ metrics $ \(AggregatedMetric (SomeInstrument (TE.decodeUtf8 . instrumentName -> name)) (MetricDatapoint ts value)) -> do
107-
forM_ metrics $ \(AggregatedMetric (CaptureInstrument _ (TE.decodeUtf8 -> name)) (MetricDatapoint ts value)) -> do
108-
LBS.hPutStr f $ encode $
109-
object
110-
[ "ph" .= ("C" :: String),
111-
"name" .= name,
112-
"ts" .= (div ts 1000),
113-
"args" .= object [name .= Number (fromIntegral value)]
114-
]
115-
LBS.hPutStr f ",\n"
116-
pure ExportSuccess
117-
)
118-
(pure ())
104+
metric_exporter <-
105+
aggregated $
106+
Exporter
107+
( \metrics -> do
108+
-- forM_ metrics $ \(AggregatedMetric (SomeInstrument (TE.decodeUtf8 . instrumentName -> name)) (MetricDatapoint ts value)) -> do
109+
forM_ metrics $ \(AggregatedMetric (CaptureInstrument _ (TE.decodeUtf8 -> name)) (MetricDatapoint ts value)) -> do
110+
LBS.hPutStr f $
111+
encode $
112+
object
113+
[ "ph" .= ("C" :: String),
114+
"name" .= name,
115+
"ts" .= (div ts 1000),
116+
"args" .= object [name .= Number (fromIntegral value)]
117+
]
118+
LBS.hPutStr f ",\n"
119+
pure ExportSuccess
120+
)
121+
(pure ())
119122
pure (span_exporter, metric_exporter)
120123

121124
data DoWeCollapseThreads = CollapseThreads | SplitThreads

opentelemetry-extra/src/OpenTelemetry/Common.hs

+34-30
Original file line numberDiff line numberDiff line change
@@ -1,25 +1,25 @@
1-
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
21
{-# LANGUAGE DeriveFunctor #-}
3-
{-# LANGUAGE LambdaCase #-}
42
{-# LANGUAGE DuplicateRecordFields #-}
3+
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4+
{-# LANGUAGE LambdaCase #-}
55
{-# LANGUAGE OverloadedStrings #-}
66

77
module OpenTelemetry.Common where
88

9+
import Control.Monad
910
import Data.Aeson
11+
import qualified Data.ByteString as BS
1012
import qualified Data.HashMap.Strict as HM
1113
import Data.Hashable
14+
import Data.IORef (modifyIORef, newIORef, readIORef)
15+
import Data.List (sortOn)
1216
import Data.String
1317
import qualified Data.Text as T
1418
import Data.Word
1519
import GHC.Generics
20+
import GHC.Int (Int8)
1621
import OpenTelemetry.SpanContext
1722
import System.Clock
18-
import Data.IORef (readIORef, modifyIORef, newIORef)
19-
import Control.Monad
20-
import Data.List (sortOn)
21-
import qualified Data.ByteString as BS
22-
import GHC.Int (Int8)
2323

2424
type Timestamp = Word64
2525

@@ -84,13 +84,15 @@ data InstrumentType
8484
| UpDownSumObserverType
8585
| ValueObserverType
8686
deriving (Show, Eq, Enum, Generic)
87+
8788
instance Hashable InstrumentType
8889

8990
data CaptureInstrument = CaptureInstrument
9091
{ instrumentType :: !InstrumentType,
9192
instrumentName :: !BS.ByteString
9293
}
9394
deriving (Show, Eq, Generic)
95+
9496
instance Hashable CaptureInstrument
9597

9698
-- | Based on https://github.com/open-telemetry/opentelemetry-proto/blob/1a931b4b57c34e7fd8f7dddcaa9b7587840e9c08/opentelemetry/proto/metrics/v1/metrics.proto#L96-L107
@@ -147,11 +149,10 @@ data ExportResult
147149
| ExportFailedNotRetryable
148150
deriving (Show, Eq)
149151

150-
data Exporter thing
151-
= Exporter
152-
{ export :: [thing] -> IO ExportResult,
153-
shutdown :: IO ()
154-
}
152+
data Exporter thing = Exporter
153+
{ export :: [thing] -> IO ExportResult,
154+
shutdown :: IO ()
155+
}
155156

156157
readInstrumentTag :: Int8 -> Maybe InstrumentType
157158
readInstrumentTag 1 = Just CounterType
@@ -179,24 +180,27 @@ aggregated (Exporter export shutdown) = do
179180
-- in, it either replaces or gets added to the current value, based on whether
180181
-- the instrument is additive.
181182
currentValuesRef <- newIORef HM.empty
182-
return $ Exporter
183-
{ export = \metrics -> do
184-
forM_ metrics $ \(Metric instrument datapoints) -> do
185-
forM_ (sortOn timestamp datapoints) $ \dp@(MetricDatapoint ts value) ->
186-
modifyIORef currentValuesRef $
187-
if additive (instrumentType instrument)
188-
then HM.alter
189-
(\case
190-
Nothing -> Just dp
191-
Just (MetricDatapoint _ oldValue) -> Just (MetricDatapoint ts $ oldValue+value))
192-
instrument
193-
else HM.insert instrument dp
194-
195-
-- Read the latest value for each instrument
196-
currentValues <- readIORef currentValuesRef
197-
export [AggregatedMetric i (currentValues HM.! i) | Metric i _ <- metrics]
198-
, shutdown
199-
}
183+
return $
184+
Exporter
185+
{ export = \metrics -> do
186+
forM_ metrics $ \(Metric instrument datapoints) -> do
187+
forM_ (sortOn timestamp datapoints) $ \dp@(MetricDatapoint ts value) ->
188+
modifyIORef currentValuesRef $
189+
if additive (instrumentType instrument)
190+
then
191+
HM.alter
192+
( \case
193+
Nothing -> Just dp
194+
Just (MetricDatapoint _ oldValue) -> Just (MetricDatapoint ts $ oldValue + value)
195+
)
196+
instrument
197+
else HM.insert instrument dp
198+
199+
-- Read the latest value for each instrument
200+
currentValues <- readIORef currentValuesRef
201+
export [AggregatedMetric i (currentValues HM.! i) | Metric i _ <- metrics],
202+
shutdown
203+
}
200204

201205
now64 :: IO Timestamp
202206
now64 = do

0 commit comments

Comments
 (0)