{-# LANGUAGE CPP #-}
{-# LANGUAGE GHCForeignImportPrim #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedFFITypes #-}
#if __GLASGOW_HASKELL__ >= 810
{-# LANGUAGE UnliftedNewtypes #-}
#endif
module Control.Concurrent.Counter.Unlifted
( Counter
, new
, get
, set
, cas
, add
, sub
, and
, or
, xor
, nand
, sameCounter
) where
import Prelude hiding (and, or)
import GHC.Exts
#include "MachDeps.h"
#ifndef SIZEOF_HSINT
#error "MachDeps.h didn't define SIZEOF_HSINT"
#endif
#define ADD_HASH(x) x#
#if defined(USE_CMM) && SIZEOF_HSINT == 8
newtype Counter s = Counter (Any :: UnliftedType)
foreign import prim "stg_newCounterzh"
new :: Int# -> State# s -> (# State# s, Counter s #)
foreign import prim "stg_atomicGetCounterzh"
get :: Counter s -> State# s -> (# State# s, Int# #)
foreign import prim "stg_atomicSetCounterzh"
set :: Counter s -> Int# -> State# s -> (# State# s #)
foreign import prim "stg_atomicAddCounterzh"
add :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
foreign import prim "stg_atomicSubCounterzh"
sub :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
foreign import prim "stg_atomicAndCounterzh"
and :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
foreign import prim "stg_atomicOrCounterzh"
or :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
foreign import prim "stg_atomicXorCounterzh"
xor :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
foreign import prim "stg_atomicNandCounterzh"
nand :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
foreign import prim "stg_casCounterzh"
cas :: Counter s -> Int# -> Int# -> State# s -> (# State# s, Int# #)
sameCounter :: Counter s -> Counter s -> Bool
sameCounter :: forall s. Counter s -> Counter s -> Bool
sameCounter (Counter Any
x) (Counter Any
y) =
Int# -> Bool
isTrue# (Any -> Any -> Int#
forall a b. a -> b -> Int#
reallyUnsafePtrEquality# Any
x Any
y)
#endif
#if !(defined(USE_CMM) && SIZEOF_HSINT == 8)
#if __GLASGOW_HASKELL__ >= 810
newtype Counter s = Counter (MutableByteArray# s)
#endif
#if !(__GLASGOW_HASKELL__ >= 810)
data Counter s = Counter (MutableByteArray# s)
#endif
{-# INLINE new #-}
new :: Int# -> State# s -> (# State# s, Counter s #)
new initVal = \s1 -> case newByteArray# ADD_HASH(SIZEOF_HSINT) s1 of
(# s2, arr #) ->
case writeIntArray# arr 0# initVal s2 of
s3 -> (# s3, Counter arr #)
{-# INLINE get #-}
get :: Counter s -> State# s -> (# State# s, Int# #)
get (Counter arr) = atomicReadIntArray# arr 0#
{-# INLINE set #-}
set :: Counter s -> Int# -> State# s -> (# State# s #)
set (Counter arr) n = \s1 -> case atomicWriteIntArray# arr 0# n s1 of
s2 -> (# s2 #)
{-# INLINE cas #-}
cas
:: Counter s
-> Int#
-> Int#
-> State# s
-> (# State# s, Int# #)
cas (Counter arr) = casIntArray# arr 0#
{-# INLINE add #-}
add :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
add (Counter arr) = fetchAddIntArray# arr 0#
{-# INLINE sub #-}
sub :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
sub (Counter arr) = fetchSubIntArray# arr 0#
{-# INLINE and #-}
and :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
and (Counter arr) = fetchAndIntArray# arr 0#
{-# INLINE or #-}
or :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
or (Counter arr) = fetchOrIntArray# arr 0#
{-# INLINE xor #-}
xor :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
xor (Counter arr) = fetchXorIntArray# arr 0#
{-# INLINE nand #-}
nand :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
nand (Counter arr) = fetchNandIntArray# arr 0#
sameCounter :: Counter s -> Counter s -> Bool
sameCounter (Counter x) (Counter y) =
isTrue# (sameMutableByteArray# x y)
#endif