
With reference to the discussion a couple of days ago about list implementations, here is some code showing the idea I was talking about... Its a list that you can write either single elements or blocks (UArrays) to, but it always reads like a list of elements, so blocks can be read in, but you can recurse over individual elements. There is obviously some overhead with this in-haskell implementation, but if this were the default list implementation in the RTS, you could use the encoding trick I mentioned before to get practically no overhead for its use. -------------------------------------------------------------- {-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-} module List where import Data.Array.Unboxed data AList a = One !a (AList a) | Many !Int !(UArray Int a) (AList a) | Nil class List l where head :: IArray UArray a => l a -> a tail :: IArray UArray a => l a -> l a (+:) :: IArray UArray a => a -> l a -> l a (++:) :: IArray UArray a => (UArray Int a) -> l a -> l a infixr 9 +: infixr 9 ++: instance List AList where head (One a _) = a head (Many i a _) = a!i tail (One _ l) = l tail (Many i a l) | i < la = (Many (i+1) a l) | otherwise = l where (_,la) = bounds a a +: l = One a l a ++: l = Many 0 a l --------------------------------------------------------------- Keean.