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.
38module Data.Atomic
49 (
@@ -12,53 +17,112 @@ 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 )
20+ #include "MachDeps.h"
21+ #ifndef SIZEOF_HSINT
22+ #error "MachDeps.h didn't define SIZEOF_HSINT"
23+ #endif
24+
1925import Prelude hiding (read , subtract )
2026
27+ import GHC.Int
28+
29+ #if SIZEOF_HSINT == 8
30+
31+ -- 64-bit imports
32+ import GHC.IO
33+ import GHC.Prim
34+
35+ #else
36+
37+ -- 32-bit imports
38+ import Data.IORef
39+
40+ #endif
41+
42+
43+ -- 64-bit machine, Int ~ Int64, do it the fast way:
44+ #if SIZEOF_HSINT == 8
45+
46+ #if MIN_VERSION_base(4,17,0)
47+ int64ToInt :: Int64 # -> Int #
48+ int64ToInt = int64ToInt#
49+
50+ intToInt64 :: Int # -> Int64 #
51+ intToInt64 = intToInt64#
52+ #else
53+ int64ToInt :: Int # -> Int #
54+ int64ToInt i = i
55+
56+ intToInt64 :: Int # -> Int #
57+ intToInt64 i = i
58+ #endif
59+
2160-- | A mutable, atomic integer.
22- newtype Atomic = C (ForeignPtr Int64 )
61+ data Atomic = C (MutableByteArray # RealWorld )
2362
2463-- | Create a new, zero initialized, atomic.
2564new :: Int64 -> IO Atomic
26- new n = do
27- fp <- mallocForeignPtr
28- withForeignPtr fp $ \ p -> poke p n
29- return $ C fp
65+ new ( I64 # n64) = IO $ \ s ->
66+ case newByteArray # SIZEOF_HSINT # s of { ( # s1, mba # ) ->
67+ case atomicWriteIntArray # mba 0 # (int64ToInt n64) s1 of { s2 ->
68+ ( # s2, C mba # ) }}
3069
3170read :: Atomic -> IO Int64
32- read (C fp ) = withForeignPtr fp cRead
33-
34- foreign import ccall unsafe " hs_atomic_read " cRead :: Ptr Int64 -> IO Int64
71+ read (C mba ) = IO $ \ s ->
72+ case atomicReadIntArray # mba 0 # s of { ( # s1, n # ) ->
73+ ( # s1, I64 # (intToInt64 n) # )}
3574
3675-- | Set the atomic to the given value.
3776write :: Atomic -> Int64 -> IO ()
38- write (C fp) n = withForeignPtr fp $ \ p -> cWrite p n
77+ write (C mba) (I64 # n64) = IO $ \ s ->
78+ case atomicWriteIntArray# mba 0 # (int64ToInt n64) s of { s1 ->
79+ (# s1, () # ) }
3980
40- foreign import ccall unsafe " hs_atomic_write" cWrite
41- :: Ptr Int64 -> Int64 -> IO ()
81+ -- | Increase the atomic by the given amount.
82+ add :: Atomic -> Int64 -> IO ()
83+ add (C mba) (I64 # n64) = IO $ \ s ->
84+ case fetchAddIntArray# mba 0 # (int64ToInt n64) s of { (# s1, _ # ) ->
85+ (# s1, () # ) }
4286
43- -- | Increase the atomic by one.
44- inc :: Atomic -> IO ()
45- inc atomic = add atomic 1
87+ -- | Decrease the atomic by the given amount.
88+ subtract :: Atomic -> Int64 -> IO ()
89+ subtract (C mba) (I64 # n64) = IO $ \ s ->
90+ case fetchSubIntArray# mba 0 # (int64ToInt n64) s of { (# s1, _ # ) ->
91+ (# s1, () # ) }
4692
47- -- | Decrease the atomic by one.
48- dec :: Atomic -> IO ()
49- dec atomic = subtract atomic 1
93+ #else
94+
95+ -- 32-bit machine, Int ~ Int32, fall back to IORef. This could be replaced with
96+ -- faster implementations for specific 32-bit machines in the future, but the
97+ -- idea is to preserve 64-bit width for counters.
98+
99+ newtype Atomic = C (IORef Int64 )
100+
101+ -- | Create a new, zero initialized, atomic.
102+ new :: Int64 -> IO Atomic
103+ new = fmap C . newIORef
104+
105+ read :: Atomic -> IO Int64
106+ read (C ior) = readIORef ior
107+
108+ -- | Set the atomic to the given value.
109+ write :: Atomic -> Int64 -> IO ()
110+ write (C ior) ! i = atomicWriteIORef ior i
50111
51112-- | Increase the atomic by the given amount.
52113add :: Atomic -> Int64 -> IO ()
53- add (C fp) n = withForeignPtr fp $ \ p -> cAdd p n
114+ add (C ior) ! i = atomicModifyIORef' ior ( \ ( ! n) -> (n + i, () ))
54115
55116-- | Decrease the atomic by the given amount.
56117subtract :: Atomic -> Int64 -> IO ()
57- subtract (C fp) n = withForeignPtr fp $ \ p -> cSubtract p n
118+ subtract (C ior) ! i = atomicModifyIORef' ior ( \ ( ! n) -> (n - i, () ))
58119
59- -- | Increase the atomic by the given amount.
60- foreign import ccall unsafe " hs_atomic_add" cAdd :: Ptr Int64 -> Int64 -> IO ()
120+ #endif
61121
62- -- | Increase the atomic by the given amount.
63- foreign import ccall unsafe " hs_atomic_subtract" cSubtract
64- :: Ptr Int64 -> Int64 -> IO ()
122+ -- | Increase the atomic by one.
123+ inc :: Atomic -> IO ()
124+ inc atomic = add atomic 1
125+
126+ -- | Decrease the atomic by one.
127+ dec :: Atomic -> IO ()
128+ dec atomic = subtract atomic 1
0 commit comments