[Haskell-cafe] Implementing ParseChart with Data.Map
Adrian Hey
ahey at iee.org
Tue Jun 3 09:28:29 EDT 2008
Hello Krasimir,
Krasimir Angelov wrote:
> 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)
>
You can do this quite easily with the AVL library, something like this
(untested code)
import Data.Cordering
import Data.Tree.AVL
type Chart k v = AVL (k, AVL v)
insert :: (Ord k, Ord v) => k -> v -> Chart k v -> Maybe (Chart k v)
insert k v tk =
case genOpenPathWith cmpk tk of
EmptyBP pthk -> Just $! insertPath pthk (k, singleton v) tk
FullBP pthk tv ->
case genOpenPath (compare v) tv of
EmptyBP pthv -> let tv' = insertPath pthv v tv
in tv' `seq` (Just $! writePath pthk (k, tv') tk)
FullBP _ _ -> Nothing
where cmpk (k',tv) = case compare k k' of
LT -> Lt
EQ -> Eq tv
GT -> Gt
..or something like that (maybe you don't want all that strictness)
The insertPath & writePath functions do involve a second traversal
but do not repeat all the comparisons. Also, provided not too much
has happened in between, they should be very fast as the nodes on
the path are probably still in cache. The important thing is that
in the case where Nothing is returned you'll have burned very little
heap.
Regards
--
Adrian Hey
More information about the Haskell-Cafe
mailing list