[Haskell-cafe] Keys and Maps [Was: Re: I just don't get it (data structures and OO)]

apfelmus apfelmus at quantentunnel.de
Wed Jun 6 10:23:02 EDT 2007


apfelmus wrote:
> I mean, if the problem is indeed to store all known
> planets in the universe, then it's indeed a database in nature and you
> have to support fine grained operations like
> 
>    delete :: Key -> Database -> Database
>    insert :: Key -> Item -> Database -> Database
>    ... and so on ...
> 
> (Note that some proposals like
> 
>   changeGalaxies $ changePlanet 0 $ changeName $ const "first"
> 
> or functional references can be interpreted as keys for 'insert' or
> 'delete'. I mean that this expression already is the key to look up a
> planet inside the universe, it's just that this key has a rather unusual
> type. And that you can compose keys.)

Here's an elaboration of the last remark which gives a Haskell-98 way to
compose keys for "nested" finite maps (like Map k (Map k' a)). It's
inspired by functional references and similar to the type-class approach.

The problem we want to solve is to access/change/delete values of type
'a' in a nested map like say Data.Map k (Data.Map k' a). Here, k and k'
are known as "keys", but we will redefine the notion "key" shortly. The
basic observation is that we need a pair (k,k') to access a value of
type 'a', just like accessing a file via an absolute path requires a
sequence of directory names. Directories can be "composed" via the well
known slash '/' and that's what we're going to do as well:

   </> :: Key m m' -> Key m' a -> Key m a

Here, a value of type

   data Key m a = ... -- abstract for now

means that it's a key to access values of type 'a' in a finite map of
type 'm' that stores theses values. In other words, we are given operations

   lookup :: Key m a -> m -> Maybe a
   insert :: Key m a -> a -> m -> m
   delete :: Key m a -> m -> m
   ...

to change the finite map at a particular key. Of course, we already have
concrete keys k for Data.Map k a. We can turn those into abstract keys
via a given embedding

   at :: k -> Key (Data.Map k a) a


Now, how to implement Key? The observation is that all operations on
keys take them as their first argument which means that we can implement
them as record selectors! For maximum generality, we use the following

  data Key m a = Key {
                   lookup    :: m -> Maybe a
                 , singleton :: a -> m
                 , alter     :: (Maybe a -> Maybe a) -> m -> m
                 }

Here, 'alter' combines the functionality of insert, delete and adjust,
which can be implemented as follows:

  insert k x = update k $ const $ Just x
  delete k   = update k $ const $ Nothing
  adjust k f = update k $ fmap f

Key composition is readily implemented as

  k </> k' = Key {
        lookup    = \m   -> lookup k m >>= lookup k'
      , singleton = \x   -> singleton k (singleton k' x)
      , alter     = \f m -> alter k (alter' f) m
      }
    where
    alter' f (Just m') = Just $ alter k' f m'
    alter' f Nothing   = f Nothing >>= singleton k'

Finally, we can implement keys for a concrete finite map implementation

  at :: k -> Key (Data.Map k a) a
  at k = Key {
        lookup    = Data.Map.lookup k
      , singleton = Data.Map.singleton k
      , alter     = flip Data.Map.alter k
      }


As an example, we have

  Just "Earth" == lookup (at "Milky Way" </> at "Sun") universe

assuming that

  universe :: Data.Map String (Data.Map String String)


Regards,
apfelmus



More information about the Haskell-Cafe mailing list