[Haskell-cafe] Implementing ParseChart with Data.Map

Krasimir Angelov kr.angelov at gmail.com
Mon Jun 2 16:35:22 EDT 2008


Hi,

I have to write ParseChart implementation with Data.Map/Set. The chart
is type like this:

type Chart k v = Map k (Set v)

now I need operation like:

insert :: k -> v -> Chart k v -> Maybe (Chart k v)

where the result is (Just _) if the (k,v) is actually added to the
chart or Nothing if it was already there and nothing have to be done.
The straight forward implementation is:

case Map.lookup k chart of
  Nothing -> Just (Map.insert k (Set.singleton v) chart)
  Just set | Set.member v set -> Nothing
               | otherwise            -> Just (Map.insert k
(Set.insert v set) chart)

The problem with this is that both the Map and the Set are traversed
twice. The first time from lookup/member and the second time from
insert. Does someone have an idea how to do this with the current
libraries?

There are the Map.updateLookupWithKey and the Map.alter functions:

updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a ->
(Maybe a,Map k a)
alter :: Ord k => (Maybe a -> Maybe a) -> k -> Map k a -> Map k a

which are the closest that I need. The problem is that the first
doesn't allow the client function to be called if there isn't matching
key in the map and the second is doesn't allow to return value from
the client function. What I really need is an alterLookúp function:

alterLookúp :: Ord k => (Maybe a -> (b,Maybe a)) -> k -> Map k a -> (b,Map k a)

The chart manipulation is in the tight loop of my application so I
need fast code. Any other ideas?

Regards,
   Krasimir


More information about the Haskell-Cafe mailing list