[Haskell-cafe] Re: dynamic arrays

Chris Kuklewicz chris at mightyreason.com
Fri Mar 17 14:31:28 EST 2006


Jared Updike wrote:
> (Moved to haskell-cafe)
> 
> JU> General question to the list:
> JU> (Q)  Are there any data structures in Haskell similar to C++/STL
> JU> vectors or C# generic Lists (i.e. strongly typed ArrayLists, e.g.
> JU> List<int>)? These data structures grow automatically as you add
> JU> elements to them (but in large chunks, not one node at a time). This
> JU> data structure (if it exists in Haskell) would run inside a monad (ST
> JU> and/or IO) and it would automaticly resize when needed, but would be
> JU> more or less like a mutable array except you can add new elements to
> JU> the end of it without reallocating an entire array of n+1 elements...
> 
> i tried to implement this today :) but there is one problem:
> 
>> if i have (l,u) - array bounds of type Ix, and i - offending index of
>> the same type, how can i compute new bounds of array so that it will
>> grow in large chunks? there is no such computation operations for
>> Ix type and that is logical - if this array is really a matrix then
>> it's hard to use the same rules of extending it as for vectors
> 
> Hmmm, that is a problem, especially as you said, for enum types that
> are bounded above. I guess you can't make it grow more than the min
> and max. For the most part, this dynamic array would only be useful
> for arrays with indices isomorphic to the natural numbers.
> 
>> such computation as (u-l)*2+l is great for integral indexes, but not
>> for general case. now i plan to use this strategy for all enum types
>> and just "grow to minimal and maximal indexes actually used" for other
>> index types
> 
> Perhaps the function to build these DynamicArrays could take a Maybe
> parameter telling the maximum possible range (for bounded enums) or
> Nothing if the array is allowed to grow indefinitely. Or an Either
> parameter where Left (a,a) tells the max range and Right (a,a) ->
> (a,a) which tells how the range should grow on a resize.
> 
> Or just the range resize function :: (a,a) -> (a,a) telling how to
> grow on a resize, i.e. for enums function = id. Something like that.
> 
>   Jared.

If I may make a suggestion: I think you have identified a need for certain
operations which would benefit from a typeclass.  The dynamic arrays need new
operations on their indices, so they need a more specific type than Ix:

class (Ix i) => IxDynamic i where
  expandSize :: (i,i) -> (i,i)
  dimensions :: i -> Int

instance IxDynamic Int where
  expandSize  (lower,upper) = (lower, 2*(upper-lower+1)+lower-1)
  dimensions _ = 1

instance (Num i,IxDynamic i,Num j, IxDynamic j) => IxDynamic (i,j) where
  expandSize ((low1,low2),(up1,up2)) =
    ((low1,low2),(2*(up1-low1+1)+low1-1,2*(up2-low2+1)+low2-1))

  dimensions (a,b) = dimensions a + dimensions b

-- This allows one to write expandVector, for instance:

data (IxDynamic i) => Vector a i e =  Vector (a i e)

-- data (MArray a e m, IxDynamic i) => Vector m a i e =  Vector (a i e)

expandVector (Vector s) = do
  let a = bounds s
      b = expandSize b
  t <- newArray_ b
  mapM_ (uncurry (writeArray t)) =<< getAssocs s
  return (Vector t)


More information about the Haskell-Cafe mailing list