STUArrays for Pairs

Manuel M T Chakravarty chak@cse.unsw.edu.au
Wed, 31 Jul 2002 23:41:34 +1000 (EST)


"Simon Marlow" <simonmar@microsoft.com> wrote,

> 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