Skip to content

Commit 4273d93

Browse files
Prototype atomic-memory-safe implementation.
1 parent c3d3616 commit 4273d93

File tree

8 files changed

+268
-173
lines changed

8 files changed

+268
-173
lines changed

Data/Atomic.hs

Lines changed: 41 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,9 @@
1-
{-# LANGUAGE BangPatterns, ForeignFunctionInterface #-}
1+
{-# LANGUAGE BangPatterns
2+
, CPP
3+
, ForeignFunctionInterface
4+
, MagicHash
5+
, UnboxedTuples
6+
#-}
27
-- | An atomic integer value. All operations are thread safe.
38
module Data.Atomic
49
(
@@ -12,33 +17,41 @@ module Data.Atomic
1217
, subtract
1318
) where
1419

15-
import Data.Int (Int64)
16-
import Foreign.ForeignPtr (ForeignPtr, mallocForeignPtr, withForeignPtr)
17-
import Foreign.Ptr (Ptr)
18-
import Foreign.Storable (poke)
1920
import Prelude hiding (read, subtract)
2021

22+
import GHC.Int
23+
import GHC.IO
24+
import GHC.Prim
25+
26+
#include "MachDeps.h"
27+
28+
#if WORD_SIZE_IN_BYTES > 32
29+
#define ARRLEN 8
30+
#else
31+
#define ARRLEN 4
32+
#endif
33+
2134
-- | A mutable, atomic integer.
22-
newtype Atomic = C (ForeignPtr Int64)
35+
--newtype Atomic = C (ForeignPtr Int64)
36+
data Atomic = C (MutableByteArray# RealWorld)
2337

2438
-- | Create a new, zero initialized, atomic.
25-
new :: Int64 -> IO Atomic
26-
new n = do
27-
fp <- mallocForeignPtr
28-
withForeignPtr fp $ \ p -> poke p n
29-
return $ C fp
39+
new :: Int -> IO Atomic
40+
new (I# n) = IO $ \s ->
41+
case newByteArray# ARRLEN# s of { (# s1, mba #) ->
42+
case atomicWriteIntArray# mba 0# n s1 of { s2 ->
43+
(# s2, C mba #) }}
3044

31-
read :: Atomic -> IO Int64
32-
read (C fp) = withForeignPtr fp cRead
33-
34-
foreign import ccall unsafe "hs_atomic_read" cRead :: Ptr Int64 -> IO Int64
45+
read :: Atomic -> IO Int
46+
read (C mba) = IO $ \s ->
47+
case atomicReadIntArray# mba 0# s of { (# s1, n #) ->
48+
(# s1, I# n #)}
3549

3650
-- | Set the atomic to the given value.
37-
write :: Atomic -> Int64 -> IO ()
38-
write (C fp) n = withForeignPtr fp $ \ p -> cWrite p n
39-
40-
foreign import ccall unsafe "hs_atomic_write" cWrite
41-
:: Ptr Int64 -> Int64 -> IO ()
51+
write :: Atomic -> Int -> IO ()
52+
write (C mba) (I# n) = IO $ \s ->
53+
case atomicWriteIntArray# mba 0# n s of { s1 ->
54+
(# s1, () #) }
4255

4356
-- | Increase the atomic by one.
4457
inc :: Atomic -> IO ()
@@ -49,16 +62,13 @@ dec :: Atomic -> IO ()
4962
dec atomic = subtract atomic 1
5063

5164
-- | Increase the atomic by the given amount.
52-
add :: Atomic -> Int64 -> IO ()
53-
add (C fp) n = withForeignPtr fp $ \ p -> cAdd p n
65+
add :: Atomic -> Int -> IO ()
66+
add (C mba) (I# n) = IO $ \s ->
67+
case fetchAddIntArray# mba 0# n s of { (# s1, _ #) ->
68+
(# s1, () #) }
5469

5570
-- | Decrease the atomic by the given amount.
56-
subtract :: Atomic -> Int64 -> IO ()
57-
subtract (C fp) n = withForeignPtr fp $ \ p -> cSubtract p n
58-
59-
-- | Increase the atomic by the given amount.
60-
foreign import ccall unsafe "hs_atomic_add" cAdd :: Ptr Int64 -> Int64 -> IO ()
61-
62-
-- | Increase the atomic by the given amount.
63-
foreign import ccall unsafe "hs_atomic_subtract" cSubtract
64-
:: Ptr Int64 -> Int64 -> IO ()
71+
subtract :: Atomic -> Int -> IO ()
72+
subtract (C mba) (I# n) = IO $ \s ->
73+
case fetchSubIntArray# mba 0# n s of { (# s1, _ #) ->
74+
(# s1, () #) }

System/Metrics.hs

Lines changed: 20 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -70,7 +70,6 @@ module System.Metrics
7070

7171
import Control.Applicative ((<$>))
7272
import Control.Monad (forM)
73-
import Data.Int (Int64)
7473
import qualified Data.IntMap.Strict as IM
7574
import Data.IORef (IORef, atomicModifyIORef, newIORef, readIORef)
7675
import qualified Data.HashMap.Strict as M
@@ -133,8 +132,8 @@ data GroupSampler = forall a. GroupSampler
133132
}
134133

135134
-- TODO: Rename this to Metric and Metric to SampledMetric.
136-
data MetricSampler = CounterS !(IO Int64)
137-
| GaugeS !(IO Int64)
135+
data MetricSampler = CounterS !(IO Int)
136+
| GaugeS !(IO Int)
138137
| LabelS !(IO T.Text)
139138
| DistributionS !(IO Distribution.Stats)
140139

@@ -156,18 +155,18 @@ newStore = do
156155
-- | Register a non-negative, monotonically increasing, integer-valued
157156
-- metric. The provided action to read the value must be thread-safe.
158157
-- Also see 'createCounter'.
159-
registerCounter :: T.Text -- ^ Counter name
160-
-> IO Int64 -- ^ Action to read the current metric value
161-
-> Store -- ^ Metric store
158+
registerCounter :: T.Text -- ^ Counter name
159+
-> IO Int -- ^ Action to read the current metric value
160+
-> Store -- ^ Metric store
162161
-> IO ()
163162
registerCounter name sample store =
164163
register name (CounterS sample) store
165164

166165
-- | Register an integer-valued metric. The provided action to read
167166
-- the value must be thread-safe. Also see 'createGauge'.
168-
registerGauge :: T.Text -- ^ Gauge name
169-
-> IO Int64 -- ^ Action to read the current metric value
170-
-> Store -- ^ Metric store
167+
registerGauge :: T.Text -- ^ Gauge name
168+
-> IO Int -- ^ Action to read the current metric value
169+
-> Store -- ^ Metric store
171170
-> IO ()
172171
registerGauge name sample store =
173172
register name (GaugeS sample) store
@@ -333,11 +332,11 @@ createDistribution name store = do
333332

334333
#if MIN_VERSION_base(4,10,0)
335334
-- | Convert nanoseconds to milliseconds.
336-
nsToMs :: Int64 -> Int64
335+
nsToMs :: Int -> Int
337336
nsToMs s = round (realToFrac s / (1000000.0 :: Double))
338337
#else
339338
-- | Convert seconds to milliseconds.
340-
sToMs :: Double -> Int64
339+
sToMs :: Double -> Int
341340
sToMs s = round (s * 1000.0)
342341
#endif
343342

@@ -430,15 +429,15 @@ registerGcMetrics store =
430429
, ("rts.gc.cumulative_bytes_used" , Counter . fromIntegral . Stats.cumulative_live_bytes)
431430
, ("rts.gc.bytes_copied" , Counter . fromIntegral . Stats.copied_bytes)
432431
#if MIN_VERSION_base(4,12,0)
433-
, ("rts.gc.init_cpu_ms" , Counter . nsToMs . Stats.init_cpu_ns)
434-
, ("rts.gc.init_wall_ms" , Counter . nsToMs . Stats.init_elapsed_ns)
432+
, ("rts.gc.init_cpu_ms" , Counter . nsToMs . fromIntegral . Stats.init_cpu_ns)
433+
, ("rts.gc.init_wall_ms" , Counter . nsToMs . fromIntegral . Stats.init_elapsed_ns)
435434
#endif
436-
, ("rts.gc.mutator_cpu_ms" , Counter . nsToMs . Stats.mutator_cpu_ns)
437-
, ("rts.gc.mutator_wall_ms" , Counter . nsToMs . Stats.mutator_elapsed_ns)
438-
, ("rts.gc.gc_cpu_ms" , Counter . nsToMs . Stats.gc_cpu_ns)
439-
, ("rts.gc.gc_wall_ms" , Counter . nsToMs . Stats.gc_elapsed_ns)
440-
, ("rts.gc.cpu_ms" , Counter . nsToMs . Stats.cpu_ns)
441-
, ("rts.gc.wall_ms" , Counter . nsToMs . Stats.elapsed_ns)
435+
, ("rts.gc.mutator_cpu_ms" , Counter . nsToMs . fromIntegral . Stats.mutator_cpu_ns)
436+
, ("rts.gc.mutator_wall_ms" , Counter . nsToMs . fromIntegral . Stats.mutator_elapsed_ns)
437+
, ("rts.gc.gc_cpu_ms" , Counter . nsToMs . fromIntegral . Stats.gc_cpu_ns)
438+
, ("rts.gc.gc_wall_ms" , Counter . nsToMs . fromIntegral . Stats.gc_elapsed_ns)
439+
, ("rts.gc.cpu_ms" , Counter . nsToMs . fromIntegral . Stats.cpu_ns)
440+
, ("rts.gc.wall_ms" , Counter . nsToMs . fromIntegral . Stats.elapsed_ns)
442441
, ("rts.gc.max_bytes_used" , Gauge . fromIntegral . Stats.max_live_bytes)
443442
, ("rts.gc.current_bytes_used" , Gauge . fromIntegral . Stats.gcdetails_live_bytes . Stats.gc)
444443
, ("rts.gc.current_bytes_slop" , Gauge . fromIntegral . Stats.gcdetails_slop_bytes . Stats.gc)
@@ -615,8 +614,8 @@ sampleGroups cbSamplers = concat `fmap` sequence (map runOne cbSamplers)
615614
return $! map (\ (n, f) -> (n, f a)) (M.toList groupSamplerMetrics)
616615

617616
-- | The value of a sampled metric.
618-
data Value = Counter {-# UNPACK #-} !Int64
619-
| Gauge {-# UNPACK #-} !Int64
617+
data Value = Counter {-# UNPACK #-} !Int
618+
| Gauge {-# UNPACK #-} !Int
620619
| Label {-# UNPACK #-} !T.Text
621620
| Distribution !Distribution.Stats
622621
deriving (Eq, Show)

System/Metrics/Counter.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,6 @@ module System.Metrics.Counter
1212
) where
1313

1414
import qualified Data.Atomic as Atomic
15-
import Data.Int (Int64)
1615
import Prelude hiding (read)
1716

1817
-- | A mutable, integer-valued counter.
@@ -23,13 +22,13 @@ new :: IO Counter
2322
new = C `fmap` Atomic.new 0
2423

2524
-- | Get the current value of the counter.
26-
read :: Counter -> IO Int64
25+
read :: Counter -> IO Int
2726
read = Atomic.read . unC
2827

2928
-- | Increase the counter by one.
3029
inc :: Counter -> IO ()
3130
inc counter = add counter 1
3231

3332
-- | Add the argument to the counter.
34-
add :: Counter -> Int64 -> IO ()
33+
add :: Counter -> Int -> IO ()
3534
add counter = Atomic.add (unC counter)

0 commit comments

Comments
 (0)