Proposed additions to Data.Map: lookupFloor and lookupCeiling

Leon Smith leon.p.smith at gmail.com
Sun Feb 28 21:27:56 EST 2010


Hi,  here are two quick, modest additions to Data.Map.   As Map is
exported abstractly,  lookupFlor can't be defined outside the library
except via splitLookup and findMax.   On the other hand,  these
implementations should be nearly the same cost as a regular lookup.

Best,
Leon

-- | /O(log n)/. Find the greatest key that is smaller or equal
-- to the given target key.   This \"floor\" key is returned, along with it's
-- associated value,  as @'Just' (key, value)@.   If the map does not have
-- a key that is smaller or equal to the target key,  then this function
-- returns 'Nothing'.

lookupFloor :: Ord k => k -> Map k a -> Maybe (k,a)
lookupFloor = go Tip
  where
    go s k t
     = case t of
        Tip -> case s of
                 Tip -> Nothing
                 Bin _ ka a _ _ -> Just (ka,a)
        Bin _ ka a l r
            -> case compare ka k of
                 LT -> go t k r
                 GT -> go s k l
                 EQ -> Just (ka,a)

-- | /O(log n)/. Find the smallest key that is greater or equal
-- to the given target key.   This \"ceiling\" key is returned, along with it's
-- associated value,  as @'Just' (key, value)@.   If the map does not have
-- a key that is greater or equal to the target key,  then this function
-- returns 'Nothing'.

lookupCeiling :: Ord k => k -> Map k a -> Maybe (k,a)
lookupCeiling = go Tip
  where
    go s k t
     = case t of
        Tip -> case s of
                 Tip -> Nothing
                 Bin _ ka a _ _ -> Just (ka,a)
        Bin _ ka a l r
            -> case compare ka k of
                 LT -> go s k r
                 GT -> go t k l
                 EQ -> Just (ka,a)


More information about the Libraries mailing list