[Haskell] TArray?

Taral taralx at gmail.com
Tue Dec 13 15:33:20 EST 2005


On 12/13/05, Sebastian Sylvan <sebastian.sylvan at gmail.com> wrote:
> There is no plan to provide an implementation of this (the
> Array-of-TVar approach) in the libs? With an MArray instance?
> It would be nice if you could just plug i into existing functions
> operating on MArray...

I hacked this up, see if it works:

{-# OPTIONS -fglasgow-exts #-}

module Control.Concurrent.STM.TMArray (
    TArray
) where

import Control.Monad (replicateM)
import Data.Array (Array)
import Data.Array.Base (listArray, arrEleBottom, unsafeAt, MArray(..),
HasBounds(..))
import Data.Ix (rangeSize)
import Control.Concurrent.STM (STM, TVar, newTVar, readTVar, writeTVar)

newtype TArray i e = TArray (Array i (TVar e))

instance MArray TArray e STM where
    newArray b e = do
        a <- replicateM (rangeSize b) (newTVar e)
        return $ TArray (listArray b a)
    newArray_ b = do
        a <- replicateM (rangeSize b) (newTVar arrEleBottom)
        return $ TArray (listArray b a)
    unsafeRead (TArray a) i = readTVar $ unsafeAt a i
    unsafeWrite (TArray a) i e = writeTVar (unsafeAt a i) e

instance HasBounds TArray where
    bounds (TArray a) = bounds a

--
Taral <taralx at gmail.com>
"Computer science is no more about computers than astronomy is about
telescopes."
    -- Edsger Dijkstra


More information about the Haskell mailing list