[Haskell-cafe] Other transactional arrays?

Emil Melnicov emilmeln at gmail.com
Fri Jul 9 06:16:20 EDT 2010


Currently, Haskell have transactional arrays in
"Control.Concurrent.STM.TArray" implemented as "Array i (TVar e)"
which is array of transactional variables.  But what if I need to
place an array into TVar itself?  This is something like "TVar
(IOArray i e)", but with ability to read/write array elements inside
an STM transaction, and then commit changes with "atomically".

I've tried to make up this arrays in the following way:

> {-# LANGUAGE MagicHash #-}
> {-# LANGUAGE UnboxedTuples #-}
> {-# OPTIONS_GHC -fno-cse #-}

> module Data.Vector.STM
>   ( TVector
>   , newTVector
>   , newTVectorIO
>   , readTVector
>   , readTVectorIO
>   , writeTVector
>   ) where

> import GHC.Conc
> import GHC.Prim
> import GHC.Types (Int(..), IO(..))

> data MutableArray a = MutableArray (MutableArray# RealWorld a)

> data TVector a = TVector (TVar# RealWorld (MutableArray a))

> stm = STM
> {-# NOINLINE stm #-}

> newTVector :: Int -> a -> STM (TVector a)
> newTVector (I# i#) x = stm $ \s1# ->
>     case newArray# i# x s1#             of { (# s2#, a# #) ->
>     case newTVar# (MutableArray a#) s2# of { (# s3#, t# #) ->
>     (# s3#, (TVector t#) #) }}

> newTVectorIO :: Int -> a -> IO (TVector a)
> newTVectorIO (I# i#) x = IO $ \s1# ->
>     case newArray# i# x s1#             of { (# s2#, a# #) ->
>     case newTVar# (MutableArray a#) s2# of { (# s3#, t# #) ->
>     (# s3#, (TVector t#) #) }}

> readTVector :: TVector a -> Int -> STM a
> readTVector (TVector t#) (I# i#) = stm $ \s1# ->
>     case readTVar# t# s1#     of { (# s2#, (MutableArray a#) #) ->
>     case readArray# a# i# s2# of { (# s3#, a #) ->
>     (# s3#, a #) }}

> readTVectorIO :: TVector a -> Int -> IO a
> readTVectorIO (TVector t#) (I# i#) = IO $ \s1# ->
>     case readTVarIO# t# s1#   of { (# s2#, (MutableArray a#) #) ->
>     case readArray# a# i# s2# of { (# s3#, a #) ->
>     (# s3#, a #) }}

> writeTVector :: TVector a -> Int -> a -> STM ()
> writeTVector (TVector t#) (I# i#) x = stm $ \s1# ->
>     case readTVar# t# s1#                    of { (# s2#, (MutableArray a#) #) ->
>     case writeArray# a# i# x s2#             of { s3# ->
>     case writeTVar# t# (MutableArray a#) s3# of { s4# ->
>     (# s4#, () #) }}}

It seems like it works, but I'm in doubt about it's correctness.
Unfortunately, I don't know much about STM mechanics, so I'm asking
Cafe users (you :-) for help.


More information about the Haskell-Cafe mailing list