Copyright | (c) Elsen Inc. 2016 |
---|---|
License | BSD3 |
Maintainer | cooper.charles.m@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This module is a drop-in replacement for Map
. It is intended to be imported as import qualified Data.Map.Extensions as Map
.
- module Data.Map
- drop :: Int -> Map k v -> Map k v
- take :: Int -> Map k v -> Map k v
- slice :: Ord k => Map k v -> k -> k -> Map k v
- slicei :: Ord k => Map k v -> Int -> Int -> Map k v
- keepKeys :: Ord k => Set k -> Map k a -> Map k a
- dropKeys :: Ord k => Set k -> Map k a -> Map k a
- filterM :: (Ord k, Monad m) => (v -> m Bool) -> Map k v -> m (Map k v)
- transpose :: (Ord a, Ord b) => Lookup2 a b v -> Lookup2 b a v
- scanl1 :: Ord k => (a -> a -> a) -> Lookup k a -> Lookup k a
- scanr1 :: Ord k => (a -> a -> a) -> Lookup k a -> Lookup k a
- groupBy :: Ord b => (a -> b) -> [a] -> Map b [a]
- groupKeysBy :: (Ord a, Ord b) => (a -> b) -> Lookup a v -> Lookup2 b a v
- groupElemsBy :: (Ord a, Ord b) => (v -> b) -> Lookup a v -> Lookup2 b a v
- fromList2 :: (Ord a, Ord b) => [(a, b, v)] -> Lookup2 a b v
- fromLists :: Ord k => [k] -> [v] -> Map k v
- lookup2 :: (Ord a, Ord b) => a -> b -> Lookup2 a b v -> Maybe v
- lookup3 :: (Ord a, Ord b, Ord c) => a -> b -> c -> Lookup3 a b c v -> Maybe v
- lookup4 :: (Ord a, Ord b, Ord c, Ord d) => a -> b -> c -> d -> Lookup4 a b c d v -> Maybe v
- type Lookup ix1 tgt = Map ix1 tgt
- type Lookup2 ix1 ix2 tgt = Map ix1 (Map ix2 tgt)
- type Lookup3 ix1 ix2 ix3 tgt = Map ix1 (Lookup2 ix2 ix3 tgt)
- type Lookup4 ix1 ix2 ix3 ix4 tgt = Lookup2 ix1 ix2 (Lookup2 ix3 ix4 tgt)
Documentation
module Data.Map
slice :: Ord k => Map k v -> k -> k -> Map k v Source #
Inclusive key-based slice. Returns a map whose keys are all between the lower and upper bounds (inclusive).
O(log n)
slicei :: Ord k => Map k v -> Int -> Int -> Map k v Source #
Inclusive index-based slice.
Run an inclusive slice given left and right indices.
if the left or right index is out of bounds,
the left index of 0
or right index of (Map.size m - 1
)
will be used respectively.
O(log n)
keepKeys :: Ord k => Set k -> Map k a -> Map k a Source #
Only keep keys that occur in the supplied Set
.
dropKeys :: Ord k => Set k -> Map k a -> Map k a Source #
Drop the keys occurring in the supplied Set
.
filterM :: (Ord k, Monad m) => (v -> m Bool) -> Map k v -> m (Map k v) Source #
This generalizes filter
to a monadic predicate.
transpose :: (Ord a, Ord b) => Lookup2 a b v -> Lookup2 b a v Source #
Transpose the first two indexes of a nested Map
.
scanl1 :: Ord k => (a -> a -> a) -> Lookup k a -> Lookup k a Source #
Perform a left scan on the values of a Map
.
Map.elems (Map.scanl1 f xs) = List.scanl1 f (Map.elems xs)
scanr1 :: Ord k => (a -> a -> a) -> Lookup k a -> Lookup k a Source #
Perform a right scan on the values of a Map
.
Map.elems (Map.scanr1 f xs) = List.scanr1 f (Map.elems xs)
groupBy :: Ord b => (a -> b) -> [a] -> Map b [a] Source #
Run a grouping function over a Map
.
The supplied function will map each element of the list to a group.
The resulting Map
will map the groups produced by the supplied function
to the lists of elements which produced that group.
Perhaps this is better illustrated by example:
>>>
let even s = s `mod` 2 == 0
>>>
groupBy even [1,2,3,4]
fromList [(False,[3,1]),(True,[4,2])]
O(n * log(n))
groupKeysBy :: (Ord a, Ord b) => (a -> b) -> Lookup a v -> Lookup2 b a v Source #
Run a grouping function over the keys of a Map
.
O(n * log(n))
groupElemsBy :: (Ord a, Ord b) => (v -> b) -> Lookup a v -> Lookup2 b a v Source #
Run a grouping function over the values of a Map
.
O(n * log(n))
fromList2 :: (Ord a, Ord b) => [(a, b, v)] -> Lookup2 a b v Source #
Generate a Lookup2 from a list of triples.
fromLists :: Ord k => [k] -> [v] -> Map k v Source #
Create a Map from a list of keys and a list of values.
fromLists ks vs = fromList (zip ks vs)
lookup2 :: (Ord a, Ord b) => a -> b -> Lookup2 a b v -> Maybe v Source #
Lookup a value two levels deep in a Lookup2
lookup3 :: (Ord a, Ord b, Ord c) => a -> b -> c -> Lookup3 a b c v -> Maybe v Source #
Lookup a value three levels deep in a Lookup3