STUArrays for Pairs

Simon Marlow simonmar@microsoft.com
Wed, 31 Jul 2002 11:28:57 +0100


> > it seems to me that if you have
> >=20
> >   instance MArray (STUArray s) a (ST s)
> >=20
> > and
> >=20
> >   instance MArray (STUArray s) b (ST s)
> >=20
> > you should be able to have
> >=20
> >   instance MArray (STUArray s) (a,b) (ST s)
> >=20
> > by simply keeping two arrays with identical bounds, one=20
> holding as and one
> > holding bs, and then when you lookup, you lookup in each=20
> individually and
> > pair.
> >=20
> > i'd like to write such an instance, but have no idea where=20
> to start...any
> > pointers?
>=20
> 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 =3D STUPairArray (STUArray s i a) (STUArray =
s
i b)

instance HasBounds (STUPairArray a b s) where
  bounds (STUPairArray left right) =3D bounds left


instance (MArray (STUArray s) a m, MArray (STUArray s) b m)
	=3D> MArray (STUPairArray a b s) (a,b) m where

  newArray (l,u) (a,b) =3D do
     lft <- newArray (l,u) a
     rgt <- newArray (l,u) b
     return (STUPairArray lft rgt)

  unsafeRead (STUPairArray lft rgt) i =3D do
     a <- unsafeRead lft i
     b <- unsafeRead rgt i
     return (a,b)

  unsafeWrite (STUPairArray lft rgt) i (a,b) =3D do
     unsafeWrite lft i a
     unsafeWrite rgt i b


Cheers,
	Simon