never executed always true always false
    1 {-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples #-}
    2 {-# OPTIONS_GHC -O2 #-}
    3 -- We always optimise this, otherwise performance of a non-optimised
    4 -- compiler is severely affected
    5 --
    6 -- (c) The University of Glasgow 2002-2006
    7 --
    8 -- Unboxed mutable Ints
    9 
   10 module GHC.Data.FastMutInt(
   11         FastMutInt, newFastMutInt,
   12         readFastMutInt, writeFastMutInt,
   13         atomicFetchAddFastMut
   14   ) where
   15 
   16 import GHC.Prelude
   17 
   18 import GHC.Base
   19 
   20 data FastMutInt = FastMutInt !(MutableByteArray# RealWorld)
   21 
   22 newFastMutInt :: Int -> IO FastMutInt
   23 newFastMutInt n = do
   24     x <- create
   25     writeFastMutInt x n
   26     return x
   27   where
   28     !(I# size) = finiteBitSize (0 :: Int) `unsafeShiftR` 3
   29     create = IO $ \s ->
   30       case newByteArray# size s of
   31         (# s, arr #) -> (# s, FastMutInt arr #)
   32 
   33 readFastMutInt :: FastMutInt -> IO Int
   34 readFastMutInt (FastMutInt arr) = IO $ \s ->
   35   case readIntArray# arr 0# s of
   36     (# s, i #) -> (# s, I# i #)
   37 
   38 writeFastMutInt :: FastMutInt -> Int -> IO ()
   39 writeFastMutInt (FastMutInt arr) (I# i) = IO $ \s ->
   40   case writeIntArray# arr 0# i s of
   41     s -> (# s, () #)
   42 
   43 atomicFetchAddFastMut :: FastMutInt -> Int -> IO Int
   44 atomicFetchAddFastMut (FastMutInt arr) (I# i) = IO $ \s ->
   45   case fetchAddIntArray# arr 0# i s of
   46     (# s, n #) -> (# s, I# n #)