{-# LANGUAGE CPP #-}
{-# LANGUAGE GHCForeignImportPrim #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE UnliftedNewtypes #-}
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 (Counter x) (Counter y) =
isTrue# (reallyUnsafePtrEquality# x y)
#else
newtype Counter s = Counter (MutableByteArray# s)
{-# INLINE new #-}
new :: Int# -> State# s -> (# State# s, Counter s #)
new :: forall s. Int# -> State# s -> (# State# s, Counter s #)
new Int#
initVal = \State# s
s1 -> case forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# ADD_HASH(SIZEOF_HSINT) s1 of
(# State# s
s2, MutableByteArray# s
arr #) ->
case forall d.
MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
writeIntArray# MutableByteArray# s
arr Int#
0# Int#
initVal State# s
s2 of
State# s
s3 -> (# State# s
s3, forall s. MutableByteArray# s -> Counter s
Counter MutableByteArray# s
arr #)
{-# INLINE get #-}
get :: Counter s -> State# s -> (# State# s, Int# #)
get :: forall s. Counter s -> State# s -> (# State# s, Int# #)
get (Counter MutableByteArray# s
arr) = forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
atomicReadIntArray# MutableByteArray# s
arr Int#
0#
{-# INLINE set #-}
set :: Counter s -> Int# -> State# s -> (# State# s #)
set :: forall s. Counter s -> Int# -> State# s -> (# State# s #)
set (Counter MutableByteArray# s
arr) Int#
n = \State# s
s1 -> case forall d.
MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
atomicWriteIntArray# MutableByteArray# s
arr Int#
0# Int#
n State# s
s1 of
State# s
s2 -> (# State# s
s2 #)
{-# INLINE cas #-}
cas
:: Counter s
-> Int#
-> Int#
-> State# s
-> (# State# s, Int# #)
cas :: forall s.
Counter s -> Int# -> Int# -> State# s -> (# State# s, Int# #)
cas (Counter MutableByteArray# s
arr) = forall d.
MutableByteArray# d
-> Int# -> Int# -> Int# -> State# d -> (# State# d, Int# #)
casIntArray# MutableByteArray# s
arr Int#
0#
{-# INLINE add #-}
add :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
add :: forall s. Counter s -> Int# -> State# s -> (# State# s, Int# #)
add (Counter MutableByteArray# s
arr) = forall d.
MutableByteArray# d
-> Int# -> Int# -> State# d -> (# State# d, Int# #)
fetchAddIntArray# MutableByteArray# s
arr Int#
0#
{-# INLINE sub #-}
sub :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
sub :: forall s. Counter s -> Int# -> State# s -> (# State# s, Int# #)
sub (Counter MutableByteArray# s
arr) = forall d.
MutableByteArray# d
-> Int# -> Int# -> State# d -> (# State# d, Int# #)
fetchSubIntArray# MutableByteArray# s
arr Int#
0#
{-# INLINE and #-}
and :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
and :: forall s. Counter s -> Int# -> State# s -> (# State# s, Int# #)
and (Counter MutableByteArray# s
arr) = forall d.
MutableByteArray# d
-> Int# -> Int# -> State# d -> (# State# d, Int# #)
fetchAndIntArray# MutableByteArray# s
arr Int#
0#
{-# INLINE or #-}
or :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
or :: forall s. Counter s -> Int# -> State# s -> (# State# s, Int# #)
or (Counter MutableByteArray# s
arr) = forall d.
MutableByteArray# d
-> Int# -> Int# -> State# d -> (# State# d, Int# #)
fetchOrIntArray# MutableByteArray# s
arr Int#
0#
{-# INLINE xor #-}
xor :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
xor :: forall s. Counter s -> Int# -> State# s -> (# State# s, Int# #)
xor (Counter MutableByteArray# s
arr) = forall d.
MutableByteArray# d
-> Int# -> Int# -> State# d -> (# State# d, Int# #)
fetchXorIntArray# MutableByteArray# s
arr Int#
0#
{-# INLINE nand #-}
nand :: Counter s -> Int# -> State# s -> (# State# s, Int# #)
nand :: forall s. Counter s -> Int# -> State# s -> (# State# s, Int# #)
nand (Counter MutableByteArray# s
arr) = forall d.
MutableByteArray# d
-> Int# -> Int# -> State# d -> (# State# d, Int# #)
fetchNandIntArray# MutableByteArray# s
arr Int#
0#
sameCounter :: Counter s -> Counter s -> Bool
sameCounter :: forall s. Counter s -> Counter s -> Bool
sameCounter (Counter MutableByteArray# s
x) (Counter MutableByteArray# s
y) =
Int# -> Bool
isTrue# (forall d. MutableByteArray# d -> MutableByteArray# d -> Int#
sameMutableByteArray# MutableByteArray# s
x MutableByteArray# s
y)
#endif