Skip to content
Snippets Groups Projects
Commit e10e9752 authored by David Feuer's avatar David Feuer Committed by konsumlamm
Browse files

Add MArray TArray e IO instance

Closes #35
parent 98215788
No related branches found
No related tags found
No related merge requests found
...@@ -23,15 +23,16 @@ module Control.Concurrent.STM.TArray ( ...@@ -23,15 +23,16 @@ module Control.Concurrent.STM.TArray (
) where ) where
import Data.Array (Array, bounds) import Data.Array (Array, bounds)
import Data.Array.Base (listArray, arrEleBottom, unsafeAt, MArray(..), import Data.Array.Base (listArray, unsafeAt, MArray(..),
IArray(numElements)) IArray(numElements))
import Data.Ix (rangeSize) import Data.Ix (rangeSize)
import Data.Typeable (Typeable) import Data.Typeable (Typeable)
import Control.Concurrent.STM.TVar (TVar, newTVar, readTVar, writeTVar) import Control.Concurrent.STM.TVar (TVar, newTVar, readTVar, writeTVar
, newTVarIO, readTVarIO)
#ifdef __GLASGOW_HASKELL__ #ifdef __GLASGOW_HASKELL__
import GHC.Conc (STM) import GHC.Conc (STM, atomically)
#else #else
import Control.Sequential.STM (STM) import Control.Sequential.STM (STM, atomically)
#endif #endif
-- |TArray is a transactional array, supporting the usual 'MArray' -- |TArray is a transactional array, supporting the usual 'MArray'
...@@ -48,13 +49,20 @@ instance MArray TArray e STM where ...@@ -48,13 +49,20 @@ instance MArray TArray e STM where
newArray b e = do newArray b e = do
a <- rep (rangeSize b) (newTVar e) a <- rep (rangeSize b) (newTVar e)
return $ TArray (listArray b a) return $ TArray (listArray b a)
newArray_ b = do
a <- rep (rangeSize b) (newTVar arrEleBottom)
return $ TArray (listArray b a)
unsafeRead (TArray a) i = readTVar $ unsafeAt a i unsafeRead (TArray a) i = readTVar $ unsafeAt a i
unsafeWrite (TArray a) i e = writeTVar (unsafeAt a i) e unsafeWrite (TArray a) i e = writeTVar (unsafeAt a i) e
getNumElements (TArray a) = return (numElements a) getNumElements (TArray a) = return (numElements a)
-- | Writes are slow in `IO`.
instance MArray TArray e IO where
getBounds (TArray a) = return (bounds a)
newArray b e = do
a <- rep (rangeSize b) (newTVarIO e)
return $ TArray (listArray b a)
unsafeRead (TArray a) i = readTVarIO $ unsafeAt a i
unsafeWrite (TArray a) i e = atomically $ writeTVar (unsafeAt a i) e
getNumElements (TArray a) = return (numElements a)
-- | Like 'replicateM' but uses an accumulator to prevent stack overflows. -- | Like 'replicateM' but uses an accumulator to prevent stack overflows.
-- Unlike 'replicateM' the returned list is in reversed order. -- Unlike 'replicateM' the returned list is in reversed order.
-- This doesn't matter though since this function is only used to create -- This doesn't matter though since this function is only used to create
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment