module System.Remote.Gauge
(
Gauge
, inc
, dec
, add
, subtract
, set
, modify
) where
import Data.IORef (atomicModifyIORef)
import Prelude hiding (subtract)
import System.Remote.Gauge.Internal
inc :: Gauge -> IO ()
inc (C ref) = do
!_ <- atomicModifyIORef ref $ \ n -> let n' = n + 1 in (n', n')
return ()
dec :: Gauge -> IO ()
dec (C ref) = do
!_ <- atomicModifyIORef ref $ \ n -> let n' = n 1 in (n', n')
return ()
add :: Gauge -> Int -> IO ()
add (C ref) i = do
!_ <- atomicModifyIORef ref $ \ n -> let n' = n + i in (n', n')
return ()
subtract :: Gauge -> Int -> IO ()
subtract (C ref) i = do
!_ <- atomicModifyIORef ref $ \ n -> let n' = n i in (n', n')
return ()
set :: Gauge -> Int -> IO ()
set (C ref) !i = atomicModifyIORef ref $ \ _ -> (i, ())
modify :: (Int -> Int) -> Gauge -> IO ()
modify f (C ref) = do
!_ <- atomicModifyIORef ref $ \ i -> let i' = f i in (i', i')
return ()