RE: STUArrays for Pairs

it seems to me that if you have
instance MArray (STUArray s) a (ST s)
and
instance MArray (STUArray s) b (ST s)
you should be able to have
instance MArray (STUArray s) (a,b) (ST s)
by simply keeping two arrays with identical bounds, one holding as and one holding bs, and then when you lookup, you lookup in each individually and pair.
i'd like to write such an instance, but have no idea where to start...any pointers?
It's a little bit more difficult, but possible. Have a look at
I'll confess I haven't looked into your stuff in any great detail, but I'm wondering whether Hal's idea can be achieved without any extra machinery. Here's my best shot; it's not entirely satisfactory because there's an extra dummy type parameter to the STUPairArray type constructor, and you need -fallow-undecidable-instances, but it seems to do the job: module PairArray where import Data.Array.Base import Control.Monad.ST data STUPairArray a b s i t = STUPairArray (STUArray s i a) (STUArray s i b) instance HasBounds (STUPairArray a b s) where bounds (STUPairArray left right) = bounds left instance (MArray (STUArray s) a m, MArray (STUArray s) b m) => MArray (STUPairArray a b s) (a,b) m where newArray (l,u) (a,b) = do lft <- newArray (l,u) a rgt <- newArray (l,u) b return (STUPairArray lft rgt) unsafeRead (STUPairArray lft rgt) i = do a <- unsafeRead lft i b <- unsafeRead rgt i return (a,b) unsafeWrite (STUPairArray lft rgt) i (a,b) = do unsafeWrite lft i a unsafeWrite rgt i b Cheers, Simon

"Simon Marlow"
I'll confess I haven't looked into your stuff in any great detail, but I'm wondering whether Hal's idea can be achieved without any extra machinery. Here's my best shot; it's not entirely satisfactory because there's an extra dummy type parameter to the STUPairArray type constructor, and you need -fallow-undecidable-instances, but it seems to do the job:
module PairArray where
import Data.Array.Base import Control.Monad.ST
data STUPairArray a b s i t = STUPairArray (STUArray s i a) (STUArray s i b)
instance HasBounds (STUPairArray a b s) where bounds (STUPairArray left right) = bounds left
instance (MArray (STUArray s) a m, MArray (STUArray s) b m) => MArray (STUPairArray a b s) (a,b) m where
newArray (l,u) (a,b) = do lft <- newArray (l,u) a rgt <- newArray (l,u) b return (STUPairArray lft rgt)
unsafeRead (STUPairArray lft rgt) i = do a <- unsafeRead lft i b <- unsafeRead rgt i return (a,b)
unsafeWrite (STUPairArray lft rgt) i (a,b) = do unsafeWrite lft i a unsafeWrite rgt i b
Not too far from how I do it. Only I use functional dependencies instead of undecidable instances. Cheers, Manuel
participants (2)
-
Manuel M T Chakravarty
-
Simon Marlow