[Haskell-cafe] Data.Map - visiting tree nodes withi a given key range ?

Olaf Klinke olf at aatal-apotheke.de
Sun Mar 15 18:42:44 UTC 2020


Dear Compl, 

there is no such function in the Data.Map.Internal module. You have to decompose the map structure yourself. 

import Data.Map.Internal

-- name clash with Control.Monad
when :: (Monoid b) => Bool -> b -> b
when t b = if t then b else mempty

contains :: Ord k => (k,k) -> k -> Bool
contains (lbound,ubound) k = lbound <= k && k <= ubound

foldRange :: (Monoid b, Ord k) => (a -> b) -> (k,k) -> Map k a -> b
foldRange f range@(lbound,ubound) m = case m of
    Tip -> mempty
    (Bin _ k a left right) -> foldLeft <> this <> foldRight where
        foldLeft  = when (lbound < k)         (foldRange f range left)
        this      = when (range `contains` k) (f a)
        foldRight = when (k < ubound)         (foldRange f range right)

-- verify that only the range is processed
>>> let m = fromList $ zip [1..] [undefined,"bar","baz",undefined]
>>> foldRange (\a -> [a]) (2,3) m
["bar","baz"]

> Am 15.03.2020 um 18:30 schrieb Compl Yue <compl.yue at icloud.com>:
> 
> Thanks Olaf,
> 
> Can you point me to the specific function for key range traversal? I went over the module doc for Data.Map.Internal and Data.Map.Strict.Internal twice, yet still don't get which one supposed to work for me, or I should ignore doc and look at the code instead ?
> 
> And the values to be scanned in specific key range are going to be consumed by some CPS mutual iterator, so fold can't be used as I see it.
> 
> Best regards,
> 
> Compl
> 
> 
> On 2020/3/15 下午9:37, Olaf Klinke wrote:
>> You can roll your own indexKeyRange using the Data.Map.Internal module which exposes the (currently used) Map implementation. Also note that if the list of values in range is to be consumed immediately, you might want to go for a fold-based function:
>> 
>> foldlWithRange :: (a -> k -> b -> a) -> (a,a) -> b -> Map k a -> b
>> 
>> Olaf



More information about the Haskell-Cafe mailing list