[Haskell-cafe] Re: Keeping an indexed collection of values?
Heinrich Apfelmus
apfelmus at quantentunnel.de
Thu Aug 20 05:57:44 EDT 2009
Job Vranish wrote:
> I've been in a situation a lot lately where I need to keep a collection of
> values, and keep track of them by a persistent index.
>
> data IndexedCollection a = IndexedCollection {
> nextKey :: Int,
> availableKeys :: [Int],
> items :: IntMap a
> } deriving (Show)
>
> emptyIndexedCollection :: IndexedCollection a
> emptyIndexedCollection = IndexedCollection 0 [] empty
>
> addItem :: a -> IndexedCollection a -> (Int, IndexedCollection a)
> addItem a (IndexedCollection nextKey' [] t) = (nextKey',
> IndexedCollection (nextKey' + 1) [] (insert nextKey' a t))
> addItem a (IndexedCollection nextKey' (k:ks) t) = (k, IndexedCollection
> nextKey' ks (insert k a t))
>
> removeItem :: Int -> IndexedCollection a -> IndexedCollection a
> removeItem k (IndexedCollection nextKey' ks t) = IndexedCollection nextKey'
> (k:ks) (delete k t)
>
> lookupItem :: Int -> IndexedCollection a -> Maybe a
> lookupItem k (IndexedCollection _ _ t) = lookup k t
>
> [...]
>
> Does anyone know of a better/already existent data structure for handling
> this problem?
>
> Or perhaps a better way of keeping a "key pool" than my availableKeys
> solution?
I'd put it in a new module and use standard names, i.e.
empty
add -- instead of insert
delete
lookup
Oh, and the name IndexedCollection is kinda long. ;)
You may want to make the nextKey field strict, so that forcing the
whole collection forces the available keys as well
data IndexedCollection = IndexedCollection {
nextKey :: !Int,
...
Otherwise, a chain of (+ 1) may linger unintentionally. If you follow
Sebastian's great suggestion, you'd need to do something like this:
empty = IndexedCollection (nats 0) IntMap.empty
where nats !n = n : nats (n+1)
Is it important that the keys are integers? If not, then I suggest
making it abstract, i.e. like this
module Store (Key, Store, empty, add, delete, lookup) where
import qualified Data.IntMap as Map
newtype Key = Key { int :: Int }
instance Show Key where show = show . int
data Store a = Store [Key] (Map.IntMap a)
empty :: Store a
empty = Store (nats 0) Map.empty
where nats !n = Key n : nats (n+1)
add :: a -> Store a -> (Key, Store a)
add a (Store (k:ks) m) = (k, Store ks $ Map.insert (int k) a m)
delete :: Key -> Store a -> Store a
delete k (Store ks m) = Store (k:ks) $ Map.delete (int k) m
lookup :: Key -> Store a -> Maybe a
lookup k (Store _ m) = Map.lookup (int k) m
This way, the user doesn't know and care how Key is implemented.
Last but not least, there is the issue that trying to use an already
deleted key might yield a wrong result instead of an error. That
shouldn't happen if used correctly, but might give a headache when
debugging.
Regards,
apfelmus
--
http://apfelmus.nfshost.com
More information about the Haskell-Cafe
mailing list