I'd like to solicit some comments on the following proposal for generalising
GHC's various array mechanisms.

The aims are twofold:

        - make it really easy to replace an existing
          (immutable) Array with a strict unboxed
          array type (i.e. just by changing the type
          of the array and letting the overloading
          machinery do the rest, we hope).

        - overload the various types of mutable arrays,
          no more newCharArray, writeStablePtrArray etc.

quick example:

        import MArray
        import Ix

        main = do
          (arr :: IOUArray Int Int) <- marray (1,10)
          sequence [ write arr i i | i <- [1..10] ]
          elts <- assocs arr
          print elts

I've attached an initial implementation (i.e an executable specification
:-), which can be dropped into fptools/hslibs/lang.  These three modules,
one of which (ArrayBase) isn't for programmer consumption, are intended to
replace the current ByteArray, MutableArray, STArray and IOArray interfaces,
and furthermore the IArray interface is intended to provide a superset of
the functionality of Haskell 98's Array module.

There are three new classes:

        class HasBounds a where
                bounds :: Ix ix => a ix e -> (ix,ix)

        class HasBounds a => IArray a e where
                (!)     :: Ix ix => a ix e -> ix -> e
                array   :: Ix ix => (ix,ix) -> [(ix,e)] -> a ix e

        class (Monad m, HasBounds a) => MArray a e m where
                read    :: Ix ix => a ix e -> ix -> m e
                write   :: Ix ix => a ix e -> ix -> e -> m ()
                marray  :: Ix ix => (ix,ix) -> m (a ix e)

where IArray is the class of immutable arrays, and MArray is the class of
mutable arrays in a given monad m.  There are three new array types, making
six altogether:

        data Array ix elt
                -- polymorphic, non-strict, immutable
                -- arrays.  Instance of IArray.
        
        data UArray ix elt      
                -- strict unboxed arrays, instances
                -- of IArray for elt types
                -- Char, Int, Word, Addr, Float etc.

        data STArray ix elt
                -- polymorphic non-strict mutable arrays
                -- instance of MArray (in monad ST)

        data STUArray ix elt
                -- strict unboxed mutable arrays in the ST monad,
                -- instances of MArray for elt types
                -- Char, Int, Word, Addr, Float etc.

        data IOArray ix elt
        data IOUArray ix elt
                -- equivalent to STArray & STUArray, 
                -- except that these are the IO versions.
                        
Have a look at the code, and let me know whether this is (a) a good idea, or
(b) the worst abuse of multiparameter type classes and constructor classes
since edison :-)

Cheesr,
        Simon

PS. The idea for IArray is Simon P.J.'s, I tacked on all the MArray stuff
too.

PPS. The names aren't very inspiring, better suggestions are welcome.

Reply via email to